ghc-7.2.2: The GHC API

TyCon

Contents

Synopsis

Main TyCon data types

data TyCon Source

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 TyCons derived from a data declaration. This includes data types with no constructors at all.

Fields

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 (see the tag assignment in DataCon.mkDataCon)

is_enum :: Bool

Cached value: is this an enumeration type? See Note [Enumeration types]

NewTyCon

Information about those TyCons derived from a newtype declaration

Fields

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 :: CoAxiom
 

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 tyConTyVars of the current TyCon (not the family one). INVARIANT: the number of types matches the arity of the family TyCon

3) A CoTyCon identifying the representation type with the type instance family

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. type family F x y :: * -> *

Coercion axiom constructors

data CoAxiom Source

A CoAxiom is a "coercion constructor", i.e. a named equality axiom.

Constructing TyCons

mkAlgTyConSource

Arguments

:: 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

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)

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

mkTupleTyConSource

Arguments

:: 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

-> 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

mkForeignTyConSource

Arguments

:: Name 
-> Maybe FastString

Name of the foreign imported thing, maybe

-> Kind 
-> Arity 
-> TyCon 

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?

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

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 -> 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?

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

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

Is this TyCon unlifted (i.e. cannot contain bottom)? Note that this can only be true for primitive and unboxed-tuple TyCons

isGadtSyntaxTyCon :: TyCon -> BoolSource

Is this an algebraic TyCon declared with the GADT syntax?

isTyConAssoc :: TyCon -> BoolSource

Are we able to extract informationa TyVar to class argument list mappping from a given TyCon?

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 dfun does that for a class instance).

Extracting information out of TyCons

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

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 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

Determine the number of value constructors a TyCon has. Panics if the TyCon is not algebraic or a tuple

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 ...

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

tyConFamilyCoercion_maybe :: TyCon -> Maybe CoAxiomSource

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)Source

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 -> 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

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

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

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)Source

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, CoAxiom)Source

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.

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 TyCon

-> Maybe ([(TyVar, tyco)], Type, [tyco])

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

makeTyConAbstract :: TyCon -> TyConSource

Make an algebraic TyCon abstract. Panics if the supplied TyCon is not algebraic

newTyConCo_maybe :: TyCon -> Maybe CoAxiomSource

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

Primitive representations of Types

data PrimRep Source

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 

tyConPrimRep :: TyCon -> PrimRepSource

Find the primitive representation of a TyCon

primRepSizeW :: PrimRep -> IntSource

Find the size of a PrimRep, in words