|
|
|
|
|
|
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
|
|
|
A data constructor
| Instances | |
|
|
|
Contains the Ids of the data constructor functions
| Constructors | |
|
|
|
Type of the tags associated with each constructor possibility
|
|
Type construction
|
|
|
:: Name | | -> Bool | Is 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
| -> 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 ...
| -> DataConIds | The Ids of the actual builder functions
| -> DataCon | | Build a new data constructor
|
|
|
|
Tags are allocated from here for real constructors
|
|
Type deconstruction
|
|
|
The representation type of the data constructor, i.e. the sort
type that will represent values of this type at runtime
|
|
|
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
|
|
|
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
|
|
|
The Name of the DataCon, giving it a unique, rooted identification
|
|
|
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
|
|
|
The tag used for ordering DataCons
|
|
|
The type constructor that we are building via this data constructor
|
|
|
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.
|
|
|
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.
|
|
|
The universally-quantified type variables of the constructor
|
|
|
The existentially-quantified type variables of the constructor
|
|
|
Both the universal and existentiatial type variables of the constructor
|
|
|
Equalities derived from the result type of the data constructor, as written
by the programmer in any GADT declaration
|
|
|
|
|
The equational constraints on the data constructor type
|
|
|
The type class and implicit parameter contsraints on the data constructor type
|
|
|
The "stupid theta" of the DataCon, such as data Eq a in:
data Eq a => T a = ...
|
|
|
:: 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
|
|
|
|
Returns the argument types of the wrapper, excluding all dictionary arguments
and without substituting for any type variables
|
|
|
|
|
Returns just the instantiated value argument types of a DataCon,
(excluding dictionary args)
|
|
|
Returns the arg types of the worker, including all dictionaries, after any
flattening has been done and without substituting for any type variables
|
|
|
The labels for the fields of this particular DataCon
|
|
|
Extract the type for any given labelled field of the DataCon
|
|
|
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
|
|
|
Strictness of existential arguments only
|
|
|
Source-level arity of the data constructor
|
|
|
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
|
|
|
Should the DataCon be presented infix?
|
|
|
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
|
|
|
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)
|
|
|
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)
|
|
|
Find all the Ids implicitly brought into scope by the data constructor. Currently,
the union of the dataConWorkId and the dataConWrapId
|
|
|
Give the demands on the arguments of a
Core constructor application (Con dc args)
|
|
Predicates on DataCons
|
|
|
Return whether there are any argument types for this DataCons original source type
|
|
|
Return whether there are any argument types for this DataCons runtime representation type
|
|
|
|
|
|
|
Vanilla DataCons are those that are nice boring Haskell 98 constructors
|
|
|
|
Splitting product types
|
|
|
:: 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
|
|
|
|
As splitProductType_maybe, but panics if the Type is not a product type
|
|
|
As deepSplitProductType_maybe, but panics if the Type is not a product type
|
|
|
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 |