|
|
|
|
|
|
Synopsis |
|
data TyCon | | type FieldLabel = Name | | | | visibleDataCons :: AlgTyConRhs -> [DataCon] | | | | | | type AssocFamilyPermutation = Maybe [Int] | | mkAlgTyCon :: Name -> Kind -> [TyVar] -> [PredType] -> AlgTyConRhs -> TyConParent -> RecFlag -> Bool -> Bool -> TyCon | | mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyCon | | mkFunTyCon :: Name -> Kind -> TyCon | | mkPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon | | mkVoidPrimTyCon :: Name -> Kind -> Arity -> TyCon | | mkLiftedPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon | | mkTupleTyCon :: Name -> Kind -> Arity -> [TyVar] -> DataCon -> Boxity -> Bool -> TyCon | | mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyCon | | mkSuperKindTyCon :: Name -> TyCon | | mkCoercionTyCon :: Name -> Arity -> ([Type] -> (Type, Type)) -> TyCon | | mkForeignTyCon :: Name -> Maybe FastString -> Kind -> Arity -> TyCon | | isAlgTyCon :: TyCon -> Bool | | isClassTyCon :: TyCon -> Bool | | isFamInstTyCon :: TyCon -> Bool | | isFunTyCon :: TyCon -> Bool | | isPrimTyCon :: TyCon -> Bool | | isTupleTyCon :: TyCon -> Bool | | isUnboxedTupleTyCon :: TyCon -> Bool | | isBoxedTupleTyCon :: TyCon -> Bool | | isSynTyCon :: TyCon -> Bool | | isClosedSynTyCon :: TyCon -> Bool | | isOpenSynTyCon :: TyCon -> Bool | | isSuperKindTyCon :: TyCon -> Bool | | isCoercionTyCon :: TyCon -> Bool | | isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, [Type] -> (Type, Type)) | | isForeignTyCon :: TyCon -> Bool | | isInjectiveTyCon :: TyCon -> Bool | | isDataTyCon :: TyCon -> Bool | | isProductTyCon :: TyCon -> Bool | | isEnumerationTyCon :: TyCon -> Bool | | isNewTyCon :: TyCon -> Bool | | isAbstractTyCon :: TyCon -> Bool | | isOpenTyCon :: TyCon -> Bool | | isUnLiftedTyCon :: TyCon -> Bool | | isGadtSyntaxTyCon :: TyCon -> Bool | | isTyConAssoc :: TyCon -> Bool | | isRecursiveTyCon :: TyCon -> Bool | | isHiBootTyCon :: TyCon -> Bool | | isImplicitTyCon :: TyCon -> Bool | | tyConHasGenerics :: TyCon -> Bool | | tyConName :: TyCon -> Name | | tyConKind :: TyCon -> Kind | | tyConUnique :: TyCon -> Unique | | tyConTyVars :: TyCon -> [TyVar] | | tyConDataCons :: TyCon -> [DataCon] | | tyConDataCons_maybe :: TyCon -> Maybe [DataCon] | | tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon | | tyConFamilySize :: TyCon -> Int | | tyConStupidTheta :: TyCon -> [PredType] | | tyConArity :: TyCon -> Arity | | tyConClass_maybe :: TyCon -> Maybe Class | | tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) | | tyConFamilyCoercion_maybe :: TyCon -> Maybe TyCon | | synTyConDefn :: TyCon -> ([TyVar], Type) | | synTyConRhs :: TyCon -> SynTyConRhs | | synTyConType :: TyCon -> Type | | synTyConResKind :: TyCon -> Kind | | tyConExtName :: TyCon -> Maybe FastString | | algTyConRhs :: TyCon -> AlgTyConRhs | | newTyConRhs :: TyCon -> ([TyVar], Type) | | newTyConEtadRhs :: TyCon -> ([TyVar], Type) | | unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, Maybe TyCon) | | assocTyConArgPoss_maybe :: TyCon -> Maybe [Int] | | tupleTyConBoxity :: TyCon -> Boxity | | tcExpandTyCon_maybe :: TyCon -> [Type] -> Maybe ([(TyVar, Type)], Type, [Type]) | | coreExpandTyCon_maybe :: TyCon -> [Type] -> Maybe ([(TyVar, Type)], Type, [Type]) | | makeTyConAbstract :: TyCon -> TyCon | | newTyConCo_maybe :: TyCon -> Maybe TyCon | | setTyConArgPoss :: [TyVar] -> TyCon -> TyCon | | | | tyConPrimRep :: TyCon -> PrimRep | | primRepSizeW :: PrimRep -> Int |
|
|
|
Main TyCon data types
|
|
|
Represents type constructors. Type constructors are introduced by things such as:
1) Data declarations: data Foo = ... creates the Foo type constructor of kind *
2) Type synonyms: type Foo = ... creates the Foo type constructor
3) Newtypes: newtype Foo a = MkFoo ... creates the Foo type constructor of kind * -> *
4) Class declarations: class Foo where creates the Foo type constructor of kind *
5) Type coercions! This is because we represent a coercion from t1 to t2 as a Type, where
that type has kind t1 ~ t2. See Coercion for more on this
This data type also encodes a number of primitive, built in type constructors such as those
for function and tuple types.
| Instances | |
|
|
|
Names of the fields in an algebraic record type
|
|
|
Represents right-hand-sides of TyCons for algebraic types
| Constructors | AbstractTyCon | Says that we know nothing about this data type, except that it's represented
by a pointer. Used when we export a data type abstractly into an .hi file.
| OpenTyCon | Represents an open type family without a fixed right hand
side. Additional instances can appear at any time.
These are introduced by either a top level declaration:
data T a :: *
Or an assoicated data type declaration, within a class declaration:
class C a b where
data T b :: *
| | DataTyCon | Information about those TyCons derived from a data declaration. This includes
data types with no constructors at all.
| data_cons :: [DataCon] | The data type constructors; can be empty if the user declares
the type to have no constructors
INVARIANT: Kept in order of increasing DataCon tag
| is_enum :: Bool | Cached value: is this an enumeration type? (See isEnumerationTyCon)
|
| NewTyCon | Information about those TyCons derived from a newtype declaration
| data_con :: DataCon | The unique constructor for the newtype. It has no existentials
| nt_rhs :: Type | Cached value: the argument type of the constructor, which
is just the representation type of the TyCon (remember that
newtypes do not exist at runtime so need a different representation
type).
The free TyVars of this type are the tyConTyVars from the corresponding
TyCon
| nt_etad_rhs :: ([TyVar], Type) | Same as the nt_rhs, but this time eta-reduced. Hence the list of TyVars in
this field may be shorter than the declared arity of the TyCon.
| nt_co :: Maybe TyCon | A TyCon (which is always a CoercionTyCon) that can have a Coercion
extracted from it to create the newtype from the representation Type.
This field is optional for non-recursive newtypes only.
|
|
|
|
|
|
Extract those DataCons that we are able to learn about. Note that visibility in this sense does not
correspond to visibility in the context of any particular user program!
Both type classes as well as family instances imply implicit
type constructors. These implicit type constructors refer to their parent
structure (ie, the class or family from which they derive) using a type of
the following form. We use TyConParent for both algebraic and synonym
types, but the variant ClassTyCon will only be used by algebraic TyCons.
|
|
|
Constructors | NoParentTyCon | An ordinary type constructor has no parent.
| ClassTyCon Class | Type constructors representing a class dictionary.
| FamilyTyCon TyCon [Type] TyCon | Type constructors representing an instance of a type family. Parameters:
1) The type family in question
2) Instance types; free variables are the tyConTyVars
of the current TyCon (not the family one). INVARIANT:
the number of types matches the arity of the family TyCon
3) A CoercionTyCon identifying the representation
type with the type instance family
|
|
|
|
|
Information pertaining to the expansion of a type synonym (type)
| Constructors | OpenSynTyCon Kind AssocFamilyPermutation | | SynonymTyCon Type | The synonym mentions head type variables. It acts as a
template for the expansion when the TyCon is applied to some
types.
|
|
|
|
|
|
Constructing TyCons
|
|
|
:: Name | | -> Kind | Kind of the resulting TyCon
| -> [TyVar] | TyVars scoped over: see tyConTyVars. Arity is inferred from the length of this list
| -> [PredType] | Stupid theta: see algTcStupidTheta
| -> AlgTyConRhs | Information about dat aconstructors
| -> TyConParent | | -> RecFlag | Is the TyCon recursive?
| -> Bool | Does it have generic functions? See hasGenerics
| -> Bool | Was the TyCon declared with GADT syntax?
| -> TyCon | | This is the making of an algebraic TyCon. Notably, you have to pass in the generic (in the -XGenerics sense)
information about the type constructor - you can get hold of it easily (see Generics module)
|
|
|
|
Simpler specialization of mkAlgTyCon for classes
|
|
|
Given the name of the function type constructor and it's kind, create the
corresponding TyCon. It is reccomended to use TypeRep.funTyCon if you want
this functionality
|
|
|
Create an unlifted primitive TyCon, such as Int#
|
|
|
Create the special void TyCon which is unlifted and has VoidRep
|
|
|
Create a lifted primitive TyCon such as RealWorld
|
|
|
:: Name | | -> Kind | Kind of the resulting TyCon
| -> Arity | Arity of the tuple
| -> [TyVar] | TyVars scoped over: see tyConTyVars
| -> DataCon | | -> Boxity | Whether the tuple is boxed or unboxed
| -> Bool | Does it have generic functions? See hasGenerics
| -> TyCon | | Foreign-imported (.NET) type constructors are represented
as primitive, but lifted, TyCons for now. They are lifted
because the Haskell type T representing the (foreign) .NET
type T is actually implemented (in ILX) as a thunkT
|
|
|
|
Create a type synonym TyCon
|
|
|
Create a super-kind TyCon
|
|
|
Create a coercion TyCon
|
|
|
|
|
Predicates on TyCons
|
|
|
Returns True if the supplied TyCon resulted from either a data or newtype declaration
|
|
|
Is this TyCon that for a class instance?
|
|
|
Is this TyCon that for a family instance, be that for a synonym or an
algebraic family instance?
|
|
|
|
|
Does this TyCon represent something that cannot be defined in Haskell?
|
|
|
Does this TyCon represent a tuple?
NB: when compiling Data.Tuple, the tycons won't reply True to
isTupleTyCon, becuase they are built as AlgTyCons. However they
get spat into the interface file as tuple tycons, so I don't think
it matters.
|
|
|
Is this the TyCon for an unboxed tuple?
|
|
|
Is this the TyCon for a boxed tuple?
|
|
|
A product TyCon must both:
1. Have one constructor
2. Not be existential
However other than this there are few restrictions: they may be data or newtype
TyCons of any boxity and may even be recursive.
Is this a TyCon representing a type synonym (type)?
|
|
|
Is this a synonym TyCon that can have no further instances appear?
|
|
|
Is this a synonym TyCon that can have may have further instances appear?
|
|
|
Is this a super-kind TyCon?
|
|
|
Is this a TyCon that represents a coercion?
|
|
|
Attempt to pull a TyCon apart into the arity and coKindFun of
a coercion TyCon. Returns Nothing if the TyCon is not of the
appropriate kind
|
|
|
Is this the TyCon of a foreign-imported type constructor?
|
|
|
Injective TyCons can be decomposed, so that
T ty1 ~ T ty2 => ty1 ~ ty2
|
|
|
Returns True for data types that are definitely represented by
heap-allocated constructors. These are scrutinised by Core-level
case expressions, and they get info tables allocated for them.
Generally, the function will be true for all data types and false
for newtypes, unboxed tuples and type family TyCons. But it is
not guarenteed to return True in all cases that it could.
NB: for a data type family, only the instance TyCons
get an info table. The family declaration TyCon does not
|
|
|
|
|
Is this an algebraic TyCon which is just an enumeration of values?
|
|
|
Is this TyCon that for a newtype
|
|
|
Test if the TyCon is algebraic but abstract (invisible data constructors)
|
|
|
Is this a TyCon, synonym or otherwise, that may have further instances appear?
|
|
|
Is this TyCon unlifted (i.e. cannot contain bottom)? Note that this can only
be true for primitive and unboxed-tuple TyCons
|
|
|
Is this an algebraic TyCon declared with the GADT syntax?
|
|
|
Are we able to extract informationa TyVar to class argument list
mappping from a given TyCon?
|
|
|
Is this a recursive TyCon?
|
|
|
Did this TyCon originate from type-checking a .h*-boot file?
|
|
|
Identifies implicit tycons that, in particular, do not go into interface
files (because they are implicitly reconstructed when the interface is
read).
Note that:
- Associated families are implicit, as they are re-constructed from
the class declaration in which they reside, and
- Family instances are not implicit as they represent the instance body
(similar to a dfun does that for a class instance).
|
|
|
Does this TyCon have any generic to/from functions available? See also hasGenerics
|
|
Extracting information out of TyCons
|
|
|
|
|
|
|
|
|
|
|
As tyConDataCons_maybe, but returns the empty list of constructors if no constructors
could be found
|
|
|
Determine the DataCons originating from the given TyCon, if the TyCon is the
sort that can have any constructors (note: this does not include abstract algebraic types)
|
|
|
If the given TyCon has a single data constructor, i.e. it is a data type with one
alternative, a tuple type or a newtype then that constructor is returned. If the TyCon
has more than one constructor, or represents a primitive or function type constructor then
Nothing is returned. In any other case, the function panics
|
|
|
Determine the number of value constructors a TyCon has. Panics if the TyCon
is not algebraic or a tuple
|
|
|
Find the "stupid theta" of the TyCon. A "stupid theta" is the context to the left of
an algebraic type declaration, e.g. Eq a in the declaration data Eq a => T a ...
|
|
|
|
|
If this TyCon is that for a class instance, return the class it is for.
Otherwise returns Nothing
|
|
|
If this TyCon is that of a family instance, return the family in question
and the instance types. Otherwise, return Nothing
|
|
|
If this TyCon is that of a family instance, return a TyCon which represents
a coercion identifying the representation type with the type instance family.
Otherwise, return Nothing
|
|
|
Extract the TyVars bound by a type synonym and the corresponding (unsubstituted) right hand side.
If the given TyCon is not a type synonym, panics
|
|
|
Extract the information pertaining to the right hand side of a type synonym (type) declaration. Panics
if the given TyCon is not a type synonym
|
|
|
Find the expansion of the type synonym represented by the given TyCon. The free variables of this
type will typically include those TyVars bound by the TyCon. Panics if the TyCon is not that of
a type synonym
|
|
|
Find the Kind of an open type synonym. Panics if the TyCon is not an open type synonym
|
|
|
Just e for foreign-imported types, holds the name of the imported thing
|
|
|
Extract an AlgTyConRhs with information about data constructors from an algebraic or tuple
TyCon. Panics for any other sort of TyCon
|
|
|
Extract the bound type variables and type expansion of a type synonym TyCon. Panics if the
TyCon is not a synonym
|
|
|
Extract the bound type variables and type expansion of an eta-contracted type synonym TyCon.
Panics if the TyCon is not a synonym
|
|
|
Take a TyCon apart into the TyVars it scopes over, the Type it expands
into, and (possibly) a coercion from the representation type to the newtype.
Returns Nothing if this is not possible.
|
|
|
Extract the mapping from TyVar indexes to indexes in the corresponding family
argument lists form an open TyCon of any sort, if the given TyCon is indeed
such a beast and that information is available
|
|
|
Extract the boxity of the given TyCon, if it is a TupleTyCon.
Panics otherwise
|
|
Manipulating TyCons
|
|
|
:: TyCon | | -> [Type] | Arguments to TyCon
| -> Maybe ([(TyVar, Type)], Type, [Type]) | Returns a TyVar substitution, the body type
of the synonym (not yet substituted) and any arguments
remaining from the application
| Used to create the view the typechecker has on TyCons. We expand (closed) synonyms only, cf. coreExpandTyCon_maybe
Used to create the view Core has on TyCons. We expand not only closed synonyms like tcExpandTyCon_maybe,
but also non-recursive newtypes
|
|
|
|
:: TyCon | | -> [Type] | Arguments to TyCon
| -> Maybe ([(TyVar, Type)], Type, [Type]) | Returns a TyVar substitution, the body type
of the synonym (not yet substituted) and any arguments
remaining from the application
|
|
|
|
Make an algebraic TyCon abstract. Panics if the supplied TyCon is not algebraic
|
|
|
Extracts the newtype coercion from such a TyCon, which can be used to construct something
with the newtypes type from its representation type (right hand side). If the supplied TyCon
is not a newtype, returns Nothing
|
|
|
Set the AssocFamilyPermutation structure in an
associated data or type synonym. The [TyVar] are the
class type variables. Remember, the tyvars of an associated
data/type are a subset of the class tyvars; except that an
associated data type can have extra type variables at the
end (see Note [Avoid name clashes for associated data types] in TcHsType)
|
|
Primitive representations of Types
|
|
|
A PrimRep is an abstraction of a type. It contains information that
the code generator needs in order to pass arguments, return results,
and store values of this type.
| Constructors | VoidRep | | PtrRep | | IntRep | Signed, word-sized value
| WordRep | Unsigned, word-sized value
| Int64Rep | Signed, 64 bit value (with 32-bit words only)
| Word64Rep | Unsigned, 64 bit value (with 32-bit words only)
| AddrRep | A pointer, but not to a Haskell value (use PtrRep)
| FloatRep | | DoubleRep | |
| Instances | |
|
|
|
Find the primitive representation of a TyCon
|
|
|
Find the size of a PrimRep, in words
|
|
Produced by Haddock version 2.6.1 |