ghc-6.12.2: The GHC APISource codeContentsIndex
DataCon
Contents
Main data types
Type construction
Type deconstruction
Predicates on DataCons
Splitting product types
Synopsis
data DataCon
data DataConIds = DCIds (Maybe Id) Id
type ConTag = Int
mkDataCon :: Name -> Bool -> [StrictnessMark] -> [FieldLabel] -> [TyVar] -> [TyVar] -> [(TyVar, Type)] -> ThetaType -> [Type] -> Type -> TyCon -> ThetaType -> DataConIds -> DataCon
fIRST_TAG :: ConTag
dataConRepType :: DataCon -> Type
dataConSig :: DataCon -> ([TyVar], ThetaType, [Type], Type)
dataConFullSig :: DataCon -> ([TyVar], [TyVar], [(TyVar, Type)], ThetaType, ThetaType, [Type], Type)
dataConName :: DataCon -> Name
dataConIdentity :: DataCon -> [Word8]
dataConTag :: DataCon -> ConTag
dataConTyCon :: DataCon -> TyCon
dataConOrigTyCon :: DataCon -> TyCon
dataConUserType :: DataCon -> Type
dataConUnivTyVars :: DataCon -> [TyVar]
dataConExTyVars :: DataCon -> [TyVar]
dataConAllTyVars :: DataCon -> [TyVar]
dataConEqSpec :: DataCon -> [(TyVar, Type)]
eqSpecPreds :: [(TyVar, Type)] -> ThetaType
dataConEqTheta :: DataCon -> ThetaType
dataConDictTheta :: DataCon -> ThetaType
dataConStupidTheta :: DataCon -> ThetaType
dataConInstArgTys :: DataCon -> [Type] -> [Type]
dataConOrigArgTys :: DataCon -> [Type]
dataConOrigResTy :: DataCon -> Type
dataConInstOrigArgTys :: DataCon -> [Type] -> [Type]
dataConRepArgTys :: DataCon -> [Type]
dataConFieldLabels :: DataCon -> [FieldLabel]
dataConFieldType :: DataCon -> FieldLabel -> Type
dataConStrictMarks :: DataCon -> [StrictnessMark]
dataConExStricts :: DataCon -> [StrictnessMark]
dataConSourceArity :: DataCon -> Arity
dataConRepArity :: DataCon -> Int
dataConIsInfix :: DataCon -> Bool
dataConWorkId :: DataCon -> Id
dataConWrapId :: DataCon -> Id
dataConWrapId_maybe :: DataCon -> Maybe Id
dataConImplicitIds :: DataCon -> [Id]
dataConRepStrictness :: DataCon -> [StrictnessMark]
isNullarySrcDataCon :: DataCon -> Bool
isNullaryRepDataCon :: DataCon -> Bool
isTupleCon :: DataCon -> Bool
isUnboxedTupleCon :: DataCon -> Bool
isVanillaDataCon :: DataCon -> Bool
classDataCon :: Class -> DataCon
splitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type])
splitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type])
deepSplitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type])
deepSplitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type])
Main data types
data DataCon Source
A data constructor
show/hide Instances
data DataConIds Source
Contains the Ids of the data constructor functions
Constructors
DCIds (Maybe Id) Id
type ConTag = IntSource
Type of the tags associated with each constructor possibility
Type construction
mkDataConSource
:: Name
-> BoolIs the constructor declared infix?
-> [StrictnessMark]Strictness annotations written in the source file
-> [FieldLabel]Field labels for the constructor, if it is a record, otherwise empty
-> [TyVar]Universally quantified type variables
-> [TyVar]Existentially quantified type variables
-> [(TyVar, Type)]GADT equalities
-> ThetaTypeTheta-type occuring before the arguments proper
-> [Type]Original argument types
-> TypeOriginal result type
-> TyConRepresentation type constructor
-> ThetaTypeThe stupid theta, context of the data declaration e.g. data Eq a => T a ...
-> DataConIdsThe Ids of the actual builder functions
-> DataCon
Build a new data constructor
fIRST_TAG :: ConTagSource
Tags are allocated from here for real constructors
Type deconstruction
dataConRepType :: DataCon -> TypeSource
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

dataConFullSig :: DataCon -> ([TyVar], [TyVar], [(TyVar, Type)], ThetaType, 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 result of dataConEqSpec

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 -> NameSource
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 -> ConTagSource
The tag used for ordering DataCons
dataConTyCon :: DataCon -> TyConSource
The type constructor that we are building via this data constructor
dataConOrigTyCon :: DataCon -> TyConSource
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 -> TypeSource

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 -> [(TyVar, Type)]Source
Equalities derived from the result type of the data constructor, as written by the programmer in any GADT declaration
eqSpecPreds :: [(TyVar, Type)] -> ThetaTypeSource
dataConEqTheta :: DataCon -> ThetaTypeSource
The equational constraints on the data constructor type
dataConDictTheta :: DataCon -> ThetaTypeSource
The type class and implicit parameter contsraints on the data constructor type
dataConStupidTheta :: DataCon -> ThetaTypeSource

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

 data Eq a => T a = ...
dataConInstArgTysSource
:: DataConA 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
dataConOrigResTy :: DataCon -> TypeSource
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 dictionaries, 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 -> FieldLabel -> TypeSource
Extract the type for any given labelled field of the DataCon
dataConStrictMarks :: DataCon -> [StrictnessMark]Source
The strictness markings decided on by the compiler. Does not include those for existential dictionaries. The list is in one-to-one correspondence with the arity of the DataCon
dataConExStricts :: DataCon -> [StrictnessMark]Source
Strictness of existential arguments only
dataConSourceArity :: DataCon -> AritySource
Source-level arity of the data constructor
dataConRepArity :: DataCon -> IntSource
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
dataConIsInfix :: DataCon -> BoolSource
Should the DataCon be presented infix?
dataConWorkId :: DataCon -> IdSource
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 -> IdSource
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 IdSource
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)
dataConImplicitIds :: DataCon -> [Id]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)
Predicates on DataCons
isNullarySrcDataCon :: DataCon -> BoolSource
Return whether there are any argument types for this DataCons original source type
isNullaryRepDataCon :: DataCon -> BoolSource
Return whether there are any argument types for this DataCons runtime representation type
isTupleCon :: DataCon -> BoolSource
isUnboxedTupleCon :: DataCon -> BoolSource
isVanillaDataCon :: DataCon -> BoolSource
Vanilla DataCons are those that are nice boring Haskell 98 constructors
classDataCon :: Class -> DataConSource
Splitting product types
splitProductType_maybeSource
:: TypeA 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

splitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type])Source
As splitProductType_maybe, but panics if the Type is not a product type
deepSplitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type])Source
As deepSplitProductType_maybe, but panics if the Type is not a product type
deepSplitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type])Source
As splitProductType_maybe, but in turn instantiates the TyCon returned and hence recursively tries to unpack it as far as it able to
Produced by Haddock version 2.6.1