ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

DataCon

Contents

Synopsis

Main data types

data DataCon Source

A data constructor

Instances

Eq DataCon 

Methods

(==) :: DataCon -> DataCon -> Bool

(/=) :: DataCon -> DataCon -> Bool

Data DataCon 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataCon -> c DataCon Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataCon Source

toConstr :: DataCon -> Constr Source

dataTypeOf :: DataCon -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c DataCon) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataCon) Source

gmapT :: (forall b. Data b => b -> b) -> DataCon -> DataCon Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataCon -> r Source

gmapQ :: (forall d. Data d => d -> u) -> DataCon -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataCon -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataCon -> m DataCon Source

Ord DataCon 
OutputableBndr DataCon 
Outputable DataCon 
Uniquable DataCon 
NamedThing DataCon 

data SrcStrictness Source

What strictness annotation the user wrote

Constructors

SrcLazy

Lazy, ie '~'

SrcStrict

Strict, ie !

NoSrcStrict

no strictness annotation

Instances

Eq SrcStrictness 
Data SrcStrictness 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcStrictness -> c SrcStrictness Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcStrictness Source

toConstr :: SrcStrictness -> Constr Source

dataTypeOf :: SrcStrictness -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c SrcStrictness) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcStrictness) Source

gmapT :: (forall b. Data b => b -> b) -> SrcStrictness -> SrcStrictness Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcStrictness -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SrcStrictness -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcStrictness -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcStrictness -> m SrcStrictness Source

Outputable SrcStrictness 
Binary SrcStrictness 

data SrcUnpackedness Source

What unpackedness the user requested

Constructors

SrcUnpack

{--} specified

SrcNoUnpack

{--} specified

NoSrcUnpack

no unpack pragma

Instances

Eq SrcUnpackedness 
Data SrcUnpackedness 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcUnpackedness -> c SrcUnpackedness Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcUnpackedness Source

toConstr :: SrcUnpackedness -> Constr Source

dataTypeOf :: SrcUnpackedness -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c SrcUnpackedness) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcUnpackedness) Source

gmapT :: (forall b. Data b => b -> b) -> SrcUnpackedness -> SrcUnpackedness Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcUnpackedness -> r Source

gmapQ :: (forall d. Data d => d -> u) -> SrcUnpackedness -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcUnpackedness -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcUnpackedness -> m SrcUnpackedness Source

Outputable SrcUnpackedness 
Binary SrcUnpackedness 

data HsSrcBang Source

Bangs on data constructor arguments as the user wrote them in the source code.

(HsSrcBang _ SrcUnpack SrcLazy) and (HsSrcBang _ SrcUnpack NoSrcStrict) (without StrictData) makes no sense, we emit a warning (in checkValidDataCon) and treat it like (HsSrcBang _ NoSrcUnpack SrcLazy)

Instances

Data HsSrcBang 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsSrcBang -> c HsSrcBang Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsSrcBang Source

toConstr :: HsSrcBang -> Constr Source

dataTypeOf :: HsSrcBang -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c HsSrcBang) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsSrcBang) Source

gmapT :: (forall b. Data b => b -> b) -> HsSrcBang -> HsSrcBang Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsSrcBang -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsSrcBang -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsSrcBang -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsSrcBang -> m HsSrcBang Source

Outputable HsSrcBang 

data HsImplBang Source

Bangs of data constructor arguments as generated by the compiler after consulting HsSrcBang, flags, etc.

Constructors

HsLazy

Lazy field

HsStrict

Strict but not unpacked field

HsUnpack (Maybe Coercion)

Strict and unpacked field co :: arg-ty ~ product-ty HsBang

Instances

Data HsImplBang 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsImplBang -> c HsImplBang Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HsImplBang Source

toConstr :: HsImplBang -> Constr Source

dataTypeOf :: HsImplBang -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c HsImplBang) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HsImplBang) Source

gmapT :: (forall b. Data b => b -> b) -> HsImplBang -> HsImplBang Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsImplBang -> r Source

gmapQ :: (forall d. Data d => d -> u) -> HsImplBang -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsImplBang -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsImplBang -> m HsImplBang Source

Outputable HsImplBang 

type ConTag = Int Source

Type of the tags associated with each constructor possibility or superclass selector

Equality specs

data EqSpec Source

An EqSpec is a tyvar/type pair representing an equality made in rejigging a GADT constructor

substEqSpec :: TCvSubst -> EqSpec -> EqSpec Source

Substitute in an EqSpec. Precondition: if the LHS of the EqSpec is mapped in the substitution, it is mapped to a type variable, not a full type.

Field labels

data FieldLbl a Source

Fields in an algebraic record type

Constructors

FieldLabel 

Fields

Instances

Functor FieldLbl 

Methods

fmap :: (a -> b) -> FieldLbl a -> FieldLbl b Source

(<$) :: a -> FieldLbl b -> FieldLbl a Source

Foldable FieldLbl 

Methods

fold :: Monoid m => FieldLbl m -> m Source

foldMap :: Monoid m => (a -> m) -> FieldLbl a -> m Source

foldr :: (a -> b -> b) -> b -> FieldLbl a -> b Source

foldr' :: (a -> b -> b) -> b -> FieldLbl a -> b Source

foldl :: (b -> a -> b) -> b -> FieldLbl a -> b Source

foldl' :: (b -> a -> b) -> b -> FieldLbl a -> b Source

foldr1 :: (a -> a -> a) -> FieldLbl a -> a Source

foldl1 :: (a -> a -> a) -> FieldLbl a -> a Source

toList :: FieldLbl a -> [a] Source

null :: FieldLbl a -> Bool Source

length :: FieldLbl a -> Int Source

elem :: Eq a => a -> FieldLbl a -> Bool Source

maximum :: Ord a => FieldLbl a -> a Source

minimum :: Ord a => FieldLbl a -> a Source

sum :: Num a => FieldLbl a -> a Source

product :: Num a => FieldLbl a -> a Source

Traversable FieldLbl 

Methods

traverse :: Applicative f => (a -> f b) -> FieldLbl a -> f (FieldLbl b) Source

sequenceA :: Applicative f => FieldLbl (f a) -> f (FieldLbl a) Source

mapM :: Monad m => (a -> m b) -> FieldLbl a -> m (FieldLbl b) Source

sequence :: Monad m => FieldLbl (m a) -> m (FieldLbl a) Source

Eq a => Eq (FieldLbl a) 

Methods

(==) :: FieldLbl a -> FieldLbl a -> Bool

(/=) :: FieldLbl a -> FieldLbl a -> Bool

Data a => Data (FieldLbl a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLbl a -> c (FieldLbl a) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLbl a) Source

toConstr :: FieldLbl a -> Constr Source

dataTypeOf :: FieldLbl a -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLbl a)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLbl a)) Source

gmapT :: (forall b. Data b => b -> b) -> FieldLbl a -> FieldLbl a Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FieldLbl a -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLbl a -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

Outputable a => Outputable (FieldLbl a) 
Binary a => Binary (FieldLbl a) 

type FieldLabelString = FastString Source

Field labels are just represented as strings; they are not necessarily unique (even within a module)

Type construction

mkDataCon Source

Arguments

:: Name 
-> Bool

Is the constructor declared infix?

-> TyConRepName

TyConRepName for the promoted TyCon

-> [HsSrcBang]

Strictness/unpack annotations, from user

-> [FieldLabel]

Field labels for the constructor, if it is a record, otherwise empty

-> [TyVar]

Universally quantified type variables

-> [TyVar]

Existentially quantified type variables

-> [EqSpec]

GADT equalities

-> ThetaType

Theta-type occuring before the arguments proper

-> [Type]

Original argument types

-> Type

Original result type

-> TyCon

Representation type constructor

-> ThetaType

The "stupid theta", context of the data declaration e.g. data Eq a => T a ...

-> Id

Worker Id

-> DataConRep

Representation

-> DataCon 

Build a new data constructor

buildAlgTyCon Source

Arguments

:: Name 
-> [TyVar]

Kind variables and type variables

-> [Role] 
-> Maybe CType 
-> ThetaType

Stupid theta

-> AlgTyConRhs 
-> RecFlag 
-> Bool

True = was declared in GADT syntax

-> AlgTyConFlav 
-> TyCon 

fIRST_TAG :: ConTag Source

Tags are allocated from here for real constructors or for superclass selectors

Type deconstruction

dataConRepType :: DataCon -> Type Source

The representation type of the data constructor, i.e. the sort type that will represent values of this type at runtime

dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type) Source

The "signature" of the DataCon returns, in order:

1) The result of dataConAllTyVars,

2) All the ThetaTypes relating to the DataCon (coercion, dictionary, implicit parameter - whatever)

3) The type arguments to the constructor

4) The original result type of the DataCon

dataConInstSig :: DataCon -> [Type] -> ([TyVar], ThetaType, [Type]) Source

Instantantiate the universal tyvars of a data con, returning the instantiated existentials, constraints, and args

dataConFullSig :: DataCon -> ([TyVar], [TyVar], [EqSpec], ThetaType, [Type], Type) Source

The "full signature" of the DataCon returns, in order:

1) The result of dataConUnivTyVars

2) The result of dataConExTyVars

3) The GADT equalities

4) The result of dataConDictTheta

5) The original argument types to the DataCon (i.e. before any change of the representation of the type)

6) The original result type of the DataCon

dataConName :: DataCon -> Name Source

The Name of the DataCon, giving it a unique, rooted identification

dataConIdentity :: DataCon -> [Word8] Source

The string package:module.name identifying a constructor, which is attached to its info table and used by the GHCi debugger and the heap profiler

dataConTag :: DataCon -> ConTag Source

The tag used for ordering DataCons

dataConTyCon :: DataCon -> TyCon Source

The type constructor that we are building via this data constructor

dataConOrigTyCon :: DataCon -> TyCon Source

The original type constructor used in the definition of this data constructor. In case of a data family instance, that will be the family type constructor.

dataConUserType :: DataCon -> Type Source

The user-declared type of the data constructor in the nice-to-read form:

T :: forall a b. a -> b -> T [a]

rather than:

T :: forall a c. forall b. (c~[a]) => a -> b -> T c

NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.

dataConUnivTyVars :: DataCon -> [TyVar] Source

The universally-quantified type variables of the constructor

dataConExTyVars :: DataCon -> [TyVar] Source

The existentially-quantified type variables of the constructor

dataConAllTyVars :: DataCon -> [TyVar] Source

Both the universal and existentiatial type variables of the constructor

dataConEqSpec :: DataCon -> [EqSpec] Source

Equalities derived from the result type of the data constructor, as written by the programmer in any GADT declaration. This includes *all* GADT-like equalities, including those written in by hand by the programmer.

dataConTheta :: DataCon -> ThetaType Source

The *full* constraints on the constructor type.

dataConStupidTheta :: DataCon -> ThetaType Source

The "stupid theta" of the DataCon, such as data Eq a in:

data Eq a => T a = ...

dataConInstArgTys Source

Arguments

:: DataCon

A datacon with no existentials or equality constraints However, it can have a dcTheta (notably it can be a class dictionary, with superclasses)

-> [Type]

Instantiated at these types

-> [Type] 

Finds the instantiated types of the arguments required to construct a DataCon representation NB: these INCLUDE any dictionary args but EXCLUDE the data-declaration context, which is discarded It's all post-flattening etc; this is a representation type

dataConOrigArgTys :: DataCon -> [Type] Source

Returns the argument types of the wrapper, excluding all dictionary arguments and without substituting for any type variables

dataConInstOrigArgTys :: DataCon -> [Type] -> [Type] Source

Returns just the instantiated value argument types of a DataCon, (excluding dictionary args)

dataConRepArgTys :: DataCon -> [Type] Source

Returns the arg types of the worker, including *all* evidence, after any flattening has been done and without substituting for any type variables

dataConFieldLabels :: DataCon -> [FieldLabel] Source

The labels for the fields of this particular DataCon

dataConFieldType :: DataCon -> FieldLabelString -> Type Source

Extract the type for any given labelled field of the DataCon

dataConSrcBangs :: DataCon -> [HsSrcBang] Source

Strictness/unpack annotations, from user; or, for imported DataCons, from the interface file The list is in one-to-one correspondence with the arity of the DataCon

dataConSourceArity :: DataCon -> Arity Source

Source-level arity of the data constructor

dataConRepArity :: DataCon -> Arity Source

Gives the number of actual fields in the representation of the data constructor. This may be more than appear in the source code; the extra ones are the existentially quantified dictionaries

dataConRepRepArity :: DataCon -> RepArity Source

The number of fields in the representation of the constructor AFTER taking into account the unpacking of any unboxed tuple fields

dataConIsInfix :: DataCon -> Bool Source

Should the DataCon be presented infix?

dataConWorkId :: DataCon -> Id Source

Get the Id of the DataCon worker: a function that is the "actual" constructor and has no top level binding in the program. The type may be different from the obvious one written in the source program. Panics if there is no such Id for this DataCon

dataConWrapId :: DataCon -> Id Source

Returns an Id which looks like the Haskell-source constructor by using the wrapper if it exists (see dataConWrapId_maybe) and failing over to the worker (see dataConWorkId)

dataConWrapId_maybe :: DataCon -> Maybe Id Source

Get the Id of the DataCon wrapper: a function that wraps the "actual" constructor so it has the type visible in the source program: c.f. dataConWorkId. Returns Nothing if there is no wrapper, which occurs for an algebraic data constructor and also for a newtype (whose constructor is inlined compulsorily)

dataConImplicitTyThings :: DataCon -> [TyThing] Source

Find all the Ids implicitly brought into scope by the data constructor. Currently, the union of the dataConWorkId and the dataConWrapId

dataConRepStrictness :: DataCon -> [StrictnessMark] Source

Give the demands on the arguments of a Core constructor application (Con dc args)

splitDataProductType_maybe Source

Arguments

:: Type

A product type, perhaps

-> Maybe (TyCon, [Type], DataCon, [Type]) 

Extract the type constructor, type argument, data constructor and it's representation argument types from a type if it is a product type.

Precisely, we return Just for any type that is all of:

  • Concrete (i.e. constructors visible)
  • Single-constructor
  • Not existentially quantified

Whether the type is a data type or a newtype

Predicates on DataCons

isNullarySrcDataCon :: DataCon -> Bool Source

Return whether there are any argument types for this DataCons original source type

isNullaryRepDataCon :: DataCon -> Bool Source

Return whether there are any argument types for this DataCons runtime representation type

isVanillaDataCon :: DataCon -> Bool Source

Vanilla DataCons are those that are nice boring Haskell 98 constructors

eqHsBang :: HsImplBang -> HsImplBang -> Bool Source

Compare strictness annotations

specialPromotedDc :: DataCon -> Bool Source

Should this DataCon be allowed in a type even without -XDataKinds? Currently, only Lifted & Unlifted

isLegacyPromotableDataCon :: DataCon -> Bool Source

Was this datacon promotable before GHC 8.0? That is, is it promotable without -XTypeInType

isLegacyPromotableTyCon :: TyCon -> Bool Source

Was this tycon promotable before GHC 8.0? That is, is it promotable without -XTypeInType

Promotion related functions