TyCon
Contents
- data TyCon
- type FieldLabel = Name
- data AlgTyConRhs
- visibleDataCons :: AlgTyConRhs -> [DataCon]
- data TyConParent
- isNoParent :: TyConParent -> Bool
- data SynTyConRhs
- data CoAxiom = CoAxiom {
- co_ax_unique :: Unique
- co_ax_name :: Name
- co_ax_tvs :: [TyVar]
- co_ax_lhs :: Type
- co_ax_rhs :: Type
- coAxiomName :: CoAxiom -> Name
- coAxiomArity :: CoAxiom -> Arity
- mkAlgTyCon :: Name -> Kind -> [TyVar] -> [PredType] -> AlgTyConRhs -> TyConParent -> RecFlag -> Bool -> TyCon
- mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyCon
- mkFunTyCon :: Name -> Kind -> TyCon
- mkPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon
- mkKindTyCon :: Name -> Kind -> TyCon
- mkLiftedPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon
- mkTupleTyCon :: Name -> Kind -> Arity -> [TyVar] -> DataCon -> Boxity -> TyCon
- mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyCon
- mkSuperKindTyCon :: Name -> TyCon
- mkForeignTyCon :: Name -> Maybe FastString -> Kind -> Arity -> TyCon
- mkAnyTyCon :: Name -> Kind -> 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
- isSuperKindTyCon :: TyCon -> Bool
- isDecomposableTyCon :: TyCon -> Bool
- isForeignTyCon :: TyCon -> Bool
- isAnyTyCon :: TyCon -> Bool
- tyConHasKind :: TyCon -> Bool
- isInjectiveTyCon :: TyCon -> Bool
- isDataTyCon :: TyCon -> Bool
- isProductTyCon :: TyCon -> Bool
- isEnumerationTyCon :: TyCon -> Bool
- isNewTyCon :: TyCon -> Bool
- isAbstractTyCon :: TyCon -> Bool
- isFamilyTyCon :: TyCon -> Bool
- isSynFamilyTyCon :: TyCon -> Bool
- isDataFamilyTyCon :: TyCon -> Bool
- isUnLiftedTyCon :: TyCon -> Bool
- isGadtSyntaxTyCon :: TyCon -> Bool
- isTyConAssoc :: TyCon -> Bool
- isRecursiveTyCon :: TyCon -> Bool
- isHiBootTyCon :: TyCon -> Bool
- isImplicitTyCon :: 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
- tyConParent :: TyCon -> TyConParent
- tyConClass_maybe :: TyCon -> Maybe Class
- tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type])
- tyConFamilyCoercion_maybe :: TyCon -> Maybe CoAxiom
- tyConFamInstSig_maybe :: TyCon -> Maybe (TyCon, [Type], CoAxiom)
- synTyConDefn :: TyCon -> ([TyVar], Type)
- synTyConRhs :: TyCon -> SynTyConRhs
- synTyConType :: TyCon -> Type
- tyConExtName :: TyCon -> Maybe FastString
- algTyConRhs :: TyCon -> AlgTyConRhs
- newTyConRhs :: TyCon -> ([TyVar], Type)
- newTyConEtadRhs :: TyCon -> ([TyVar], Type)
- unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, CoAxiom)
- tupleTyConBoxity :: TyCon -> Boxity
- tupleTyConArity :: TyCon -> Arity
- tcExpandTyCon_maybe, coreExpandTyCon_maybe :: TyCon -> [tyco] -> Maybe ([(TyVar, tyco)], Type, [tyco])
- makeTyConAbstract :: TyCon -> TyCon
- newTyConCo :: TyCon -> CoAxiom
- newTyConCo_maybe :: TyCon -> Maybe CoAxiom
- data PrimRep
- tyConPrimRep :: TyCon -> PrimRep
- primRepSizeW :: PrimRep -> Int
Main TyCon data types
TyCons represent 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 *
This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.
type FieldLabel = NameSource
Names of the fields in an algebraic record type
data AlgTyConRhs Source
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. |
| DataFamilyTyCon | 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 associated data type declaration, within a class declaration: class C a b where data T b :: * |
| DataTyCon | Information about those |
Fields
| |
| NewTyCon | Information about those |
Fields
| |
visibleDataCons :: AlgTyConRhs -> [DataCon]Source
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.
data TyConParent Source
Constructors
| NoParentTyCon | An ordinary type constructor has no parent. |
| ClassTyCon Class | Type constructors representing a class dictionary. |
| AssocFamilyTyCon Class | An *associated* type of a class. |
| FamInstTyCon TyCon [Type] CoAxiom | Type constructors representing an instance of a type family. Parameters: 1) The type family in question 2) Instance types; free variables are the 3) A |
isNoParent :: TyConParent -> BoolSource
data SynTyConRhs Source
Information pertaining to the expansion of a type synonym (type)
Constructors
| SynonymTyCon Type | An ordinary type synonyn. |
| SynFamilyTyCon | A type synonym family e.g. |
Coercion axiom constructors
A CoAxiom is a "coercion constructor", i.e. a named equality axiom.
coAxiomName :: CoAxiom -> NameSource
coAxiomArity :: CoAxiom -> AritySource
Constructing TyCons
Arguments
| :: Name | |
| -> Kind | Kind of the resulting |
| -> [TyVar] |
|
| -> [PredType] | Stupid theta: see |
| -> AlgTyConRhs | Information about dat aconstructors |
| -> TyConParent | |
| -> RecFlag | Is the |
| -> Bool | Was the |
| -> 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)
mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyConSource
Simpler specialization of mkAlgTyCon for classes
mkFunTyCon :: Name -> Kind -> TyConSource
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
mkPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyConSource
Create an unlifted primitive TyCon, such as Int#
mkKindTyCon :: Name -> Kind -> TyConSource
Kind constructors
mkLiftedPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyConSource
Create a lifted primitive TyCon such as RealWorld
Arguments
| :: Name | |
| -> Kind | Kind of the resulting |
| -> Arity | Arity of the tuple |
| -> [TyVar] |
|
| -> DataCon | |
| -> Boxity | Whether the tuple is boxed or unboxed |
| -> 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
mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyConSource
Create a type synonym TyCon
mkSuperKindTyCon :: Name -> TyConSource
Create a super-kind TyCon
mkAnyTyCon :: Name -> Kind -> TyConSource
Predicates on TyCons
isAlgTyCon :: TyCon -> BoolSource
Returns True if the supplied TyCon resulted from either a
data or newtype declaration
isClassTyCon :: TyCon -> BoolSource
Is this TyCon that for a class instance?
isFamInstTyCon :: TyCon -> BoolSource
Is this TyCon that for a family instance, be that for a synonym or an
algebraic family instance?
isFunTyCon :: TyCon -> BoolSource
isPrimTyCon :: TyCon -> BoolSource
Does this TyCon represent something that cannot be defined in Haskell?
isTupleTyCon :: TyCon -> BoolSource
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.
isUnboxedTupleTyCon :: TyCon -> BoolSource
Is this the TyCon for an unboxed tuple?
isBoxedTupleTyCon :: TyCon -> BoolSource
Is this the TyCon for a boxed tuple?
isSynTyCon :: TyCon -> BoolSource
isClosedSynTyCon :: TyCon -> BoolSource
Is this a synonym TyCon that can have no further instances appear?
isSuperKindTyCon :: TyCon -> BoolSource
Is this a super-kind TyCon?
isForeignTyCon :: TyCon -> BoolSource
Is this the TyCon of a foreign-imported type constructor?
isAnyTyCon :: TyCon -> BoolSource
Is this an AnyTyCon?
tyConHasKind :: TyCon -> BoolSource
isInjectiveTyCon :: TyCon -> BoolSource
Injective TyCons can be decomposed, so that
T ty1 ~ T ty2 => ty1 ~ ty2
isDataTyCon :: TyCon -> BoolSource
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
isProductTyCon :: TyCon -> BoolSource
isEnumerationTyCon :: TyCon -> BoolSource
Is this an algebraic TyCon which is just an enumeration of values?
isNewTyCon :: TyCon -> BoolSource
Is this TyCon that for a newtype
isAbstractTyCon :: TyCon -> BoolSource
Test if the TyCon is algebraic but abstract (invisible data constructors)
isFamilyTyCon :: TyCon -> BoolSource
Is this a TyCon, synonym or otherwise, that may have further instances appear?
isSynFamilyTyCon :: TyCon -> BoolSource
Is this a synonym TyCon that can have may have further instances appear?
isDataFamilyTyCon :: TyCon -> BoolSource
Is this a synonym TyCon that can have may have further instances appear?
isUnLiftedTyCon :: TyCon -> BoolSource
isGadtSyntaxTyCon :: TyCon -> BoolSource
Is this an algebraic TyCon declared with the GADT syntax?
isTyConAssoc :: TyCon -> BoolSource
isRecursiveTyCon :: TyCon -> BoolSource
Is this a recursive TyCon?
isHiBootTyCon :: TyCon -> BoolSource
Did this TyCon originate from type-checking a .h*-boot file?
isImplicitTyCon :: TyCon -> BoolSource
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
dfundoes that for a class instance).
Extracting information out of TyCons
tyConUnique :: TyCon -> UniqueSource
tyConTyVars :: TyCon -> [TyVar]Source
tyConDataCons :: TyCon -> [DataCon]Source
As tyConDataCons_maybe, but returns the empty list of constructors if no constructors
could be found
tyConDataCons_maybe :: TyCon -> Maybe [DataCon]Source
tyConSingleDataCon_maybe :: TyCon -> Maybe DataConSource
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
tyConFamilySize :: TyCon -> IntSource
tyConStupidTheta :: TyCon -> [PredType]Source
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 ...
tyConArity :: TyCon -> AritySource
tyConClass_maybe :: TyCon -> Maybe ClassSource
If this TyCon is that for a class instance, return the class it is for.
Otherwise returns Nothing
tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type])Source
If this TyCon is that of a family instance, return the family in question
and the instance types. Otherwise, return Nothing
synTyConDefn :: TyCon -> ([TyVar], Type)Source
synTyConRhs :: TyCon -> SynTyConRhsSource
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
synTyConType :: TyCon -> TypeSource
tyConExtName :: TyCon -> Maybe FastStringSource
Just e for foreign-imported types,
holds the name of the imported thing
algTyConRhs :: TyCon -> AlgTyConRhsSource
Extract an AlgTyConRhs with information about data constructors from an algebraic or tuple
TyCon. Panics for any other sort of TyCon
newTyConRhs :: TyCon -> ([TyVar], Type)Source
newTyConEtadRhs :: TyCon -> ([TyVar], Type)Source
tupleTyConBoxity :: TyCon -> BoxitySource
Extract the boxity of the given TyCon, if it is a TupleTyCon.
Panics otherwise
tupleTyConArity :: TyCon -> AritySource
Extract the arity of the given TyCon, if it is a TupleTyCon.
Panics otherwise
Manipulating TyCons
tcExpandTyCon_maybe,coreExpandTyCon_maybeSource
Arguments
| :: TyCon | |
| -> [tyco] | Arguments to |
| -> Maybe ([(TyVar, tyco)], Type, [tyco]) | Returns a |
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
newTyConCo :: TyCon -> CoAxiomSource
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.
tyConPrimRep :: TyCon -> PrimRepSource
Find the primitive representation of a TyCon
primRepSizeW :: PrimRep -> IntSource
Find the size of a PrimRep, in words