| |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
Synopsis | |||||||||||||||||||||||||||||||
Main TyCon data types | |||||||||||||||||||||||||||||||
data TyCon | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
type FieldLabel = Name | |||||||||||||||||||||||||||||||
Names of the fields in an algebraic record type | |||||||||||||||||||||||||||||||
data AlgTyConRhs | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
visibleDataCons :: AlgTyConRhs -> [DataCon] | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
data SynTyConRhs | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
type AssocFamilyPermutation = Maybe [Int] | |||||||||||||||||||||||||||||||
Constructing TyCons | |||||||||||||||||||||||||||||||
mkAlgTyCon | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
mkClassTyCon :: Name -> Kind -> [TyVar] -> AlgTyConRhs -> Class -> RecFlag -> TyCon | |||||||||||||||||||||||||||||||
Simpler specialization of mkAlgTyCon for classes | |||||||||||||||||||||||||||||||
mkFunTyCon :: Name -> Kind -> TyCon | |||||||||||||||||||||||||||||||
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 -> TyCon | |||||||||||||||||||||||||||||||
Create an unlifted primitive TyCon, such as Int# | |||||||||||||||||||||||||||||||
mkVoidPrimTyCon :: Name -> Kind -> Arity -> TyCon | |||||||||||||||||||||||||||||||
Create the special void TyCon which is unlifted and has VoidRep | |||||||||||||||||||||||||||||||
mkLiftedPrimTyCon :: Name -> Kind -> Arity -> PrimRep -> TyCon | |||||||||||||||||||||||||||||||
Create a lifted primitive TyCon such as RealWorld | |||||||||||||||||||||||||||||||
mkTupleTyCon | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
mkSynTyCon :: Name -> Kind -> [TyVar] -> SynTyConRhs -> TyConParent -> TyCon | |||||||||||||||||||||||||||||||
Create a type synonym TyCon | |||||||||||||||||||||||||||||||
mkSuperKindTyCon :: Name -> TyCon | |||||||||||||||||||||||||||||||
Create a super-kind TyCon | |||||||||||||||||||||||||||||||
mkCoercionTyCon :: Name -> Arity -> ([Type] -> (Type, Type)) -> TyCon | |||||||||||||||||||||||||||||||
Create a coercion TyCon | |||||||||||||||||||||||||||||||
mkForeignTyCon | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
Predicates on TyCons | |||||||||||||||||||||||||||||||
isAlgTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Returns True if the supplied TyCon resulted from either a data or newtype declaration | |||||||||||||||||||||||||||||||
isClassTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this TyCon that for a class instance? | |||||||||||||||||||||||||||||||
isFamInstTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this TyCon that for a family instance, be that for a synonym or an algebraic family instance? | |||||||||||||||||||||||||||||||
isFunTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
isPrimTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Does this TyCon represent something that cannot be defined in Haskell? | |||||||||||||||||||||||||||||||
isTupleTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
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 -> Bool | |||||||||||||||||||||||||||||||
Is this the TyCon for an unboxed tuple? | |||||||||||||||||||||||||||||||
isBoxedTupleTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this the TyCon for a boxed tuple? | |||||||||||||||||||||||||||||||
isSynTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
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)? | |||||||||||||||||||||||||||||||
isClosedSynTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a synonym TyCon that can have no further instances appear? | |||||||||||||||||||||||||||||||
isOpenSynTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a synonym TyCon that can have may have further instances appear? | |||||||||||||||||||||||||||||||
isSuperKindTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a super-kind TyCon? | |||||||||||||||||||||||||||||||
isCoercionTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a TyCon that represents a coercion? | |||||||||||||||||||||||||||||||
isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, [Type] -> (Type, Type)) | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
isForeignTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this the TyCon of a foreign-imported type constructor? | |||||||||||||||||||||||||||||||
isDataTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
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 -> Bool | |||||||||||||||||||||||||||||||
isEnumerationTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this an algebraic TyCon which is just an enumeration of values? | |||||||||||||||||||||||||||||||
isNewTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this TyCon that for a newtype | |||||||||||||||||||||||||||||||
isAbstractTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Test if the TyCon is algebraic but abstract (invisible data constructors) | |||||||||||||||||||||||||||||||
isOpenTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a TyCon, synonym or otherwise, that may have further instances appear? | |||||||||||||||||||||||||||||||
isUnLiftedTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this TyCon unlifted (i.e. cannot contain bottom)? Note that this can only be true for primitive and unboxed-tuple TyCons | |||||||||||||||||||||||||||||||
isGadtSyntaxTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this an algebraic TyCon declared with the GADT syntax? | |||||||||||||||||||||||||||||||
isTyConAssoc :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Are we able to extract informationa TyVar to class argument list mappping from a given TyCon? | |||||||||||||||||||||||||||||||
isRecursiveTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Is this a recursive TyCon? | |||||||||||||||||||||||||||||||
isHiBootTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Did this TyCon originate from type-checking a .h*-boot file? | |||||||||||||||||||||||||||||||
isImplicitTyCon :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Identifies implicit tycons that, in particular, do not go into interface files (because they are implicitly reconstructed when the interface is read). Note that:
| |||||||||||||||||||||||||||||||
tyConHasGenerics :: TyCon -> Bool | |||||||||||||||||||||||||||||||
Does this TyCon have any generic to/from functions available? See also hasGenerics | |||||||||||||||||||||||||||||||
Extracting information out of TyCons | |||||||||||||||||||||||||||||||
tyConName :: TyCon -> Name | |||||||||||||||||||||||||||||||
tyConKind :: TyCon -> Kind | |||||||||||||||||||||||||||||||
tyConUnique :: TyCon -> Unique | |||||||||||||||||||||||||||||||
tyConTyVars :: TyCon -> [TyVar] | |||||||||||||||||||||||||||||||
tyConDataCons :: TyCon -> [DataCon] | |||||||||||||||||||||||||||||||
As tyConDataCons_maybe, but returns the empty list of constructors if no constructors could be found | |||||||||||||||||||||||||||||||
tyConDataCons_maybe :: TyCon -> Maybe [DataCon] | |||||||||||||||||||||||||||||||
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) | |||||||||||||||||||||||||||||||
tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon | |||||||||||||||||||||||||||||||
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 -> Int | |||||||||||||||||||||||||||||||
Determine the number of value constructors a TyCon has. Panics if the TyCon is not algebraic or a tuple | |||||||||||||||||||||||||||||||
tyConSelIds :: TyCon -> [Id] | |||||||||||||||||||||||||||||||
Extract the record selector Ids from an algebraic TyCon and returns the empty list otherwise | |||||||||||||||||||||||||||||||
tyConStupidTheta :: TyCon -> [PredType] | |||||||||||||||||||||||||||||||
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 -> Arity | |||||||||||||||||||||||||||||||
tyConClass_maybe :: TyCon -> Maybe Class | |||||||||||||||||||||||||||||||
If this TyCon is that for a class instance, return the class it is for. Otherwise returns Nothing | |||||||||||||||||||||||||||||||
tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) | |||||||||||||||||||||||||||||||
If this TyCon is that of a family instance, return the family in question and the instance types. Otherwise, return Nothing | |||||||||||||||||||||||||||||||
tyConFamilyCoercion_maybe :: TyCon -> Maybe TyCon | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
synTyConDefn :: TyCon -> ([TyVar], Type) | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
synTyConRhs :: TyCon -> SynTyConRhs | |||||||||||||||||||||||||||||||
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 -> Type | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
synTyConResKind :: TyCon -> Kind | |||||||||||||||||||||||||||||||
Find the Kind of an open type synonym. Panics if the TyCon is not an open type synonym | |||||||||||||||||||||||||||||||
tyConExtName :: TyCon -> Maybe FastString | |||||||||||||||||||||||||||||||
Just e for foreign-imported types, holds the name of the imported thing | |||||||||||||||||||||||||||||||
algTyConRhs :: TyCon -> AlgTyConRhs | |||||||||||||||||||||||||||||||
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) | |||||||||||||||||||||||||||||||
Extract the bound type variables and type expansion of a type synonym TyCon. Panics if the TyCon is not a synonym | |||||||||||||||||||||||||||||||
newTyConEtadRhs :: TyCon -> ([TyVar], Type) | |||||||||||||||||||||||||||||||
Extract the bound type variables and type expansion of an eta-contracted type synonym TyCon. Panics if the TyCon is not a synonym | |||||||||||||||||||||||||||||||
unwrapNewTyCon_maybe :: TyCon -> Maybe ([TyVar], Type, Maybe TyCon) | |||||||||||||||||||||||||||||||
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. | |||||||||||||||||||||||||||||||
assocTyConArgPoss_maybe :: TyCon -> Maybe [Int] | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
tupleTyConBoxity :: TyCon -> Boxity | |||||||||||||||||||||||||||||||
Extract the boxity of the given TyCon, if it is a TupleTyCon. Panics otherwise | |||||||||||||||||||||||||||||||
Manipulating TyCons | |||||||||||||||||||||||||||||||
tcExpandTyCon_maybe | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
coreExpandTyCon_maybe | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
makeTyConAbstract :: TyCon -> TyCon | |||||||||||||||||||||||||||||||
Make an algebraic TyCon abstract. Panics if the supplied TyCon is not algebraic | |||||||||||||||||||||||||||||||
newTyConCo_maybe :: TyCon -> Maybe TyCon | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
setTyConArgPoss :: [TyVar] -> TyCon -> TyCon | |||||||||||||||||||||||||||||||
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 | |||||||||||||||||||||||||||||||
data PrimRep | |||||||||||||||||||||||||||||||
| |||||||||||||||||||||||||||||||
tyConPrimRep :: TyCon -> PrimRep | |||||||||||||||||||||||||||||||
Find the primitive representation of a TyCon | |||||||||||||||||||||||||||||||
primRepSizeW :: PrimRep -> Int | |||||||||||||||||||||||||||||||
Find the size of a PrimRep, in words | |||||||||||||||||||||||||||||||
Produced by Haddock version 2.4.2 |