GHC essentially supports two type systems: (1) the source type system (which is a heavily extended version of the type system of Haskell 98) and (2) the Core type system, which is the type system used by the intermediate language (see also Sugar Free: From Haskell To Core).
During parsing and renaming, type information is represented in a form
that is very close to Haskell's concrete syntax; it is defined by
HsTypes.HsType
. In addition, type, class, and instance
declarations are maintained in their source form as defined in the
module HsDecl
. The situation changes during type checking,
where types are translated into a second representation, which is
defined in the module types/TypeRep.lhs
, as type
Type
. This second representation is peculiar in that it is
a hybrid between the source representation of types and the Core
representation of types. Using functions, such as
Type.coreView
and Type.deepCoreView
, a value
of type Type
exhibits its Core representation. On the
other hand, pretty printing a Type
with
TypeRep.pprType
yields the type's source representation.
In fact, the type checker maintains type
environments based on Type
, but needs to perform type
checking on source-level types. As a result, we have functions
Type.tcEqType
and Type.tcCmpType
, which
compare types based on their source representation, as well as the
function coreEqType
, which compares them based on their
core representation. The latter is needed during type checking of Core
(as performed by the functions in the module
coreSyn/CoreLint.lhs
).
Type synonyms in Haskell are essentially a form of macro definitions on
the type level. For example, when the type checker compares two type
terms, synonyms are always compared in their expanded form. However, to
produce good error messages, we like to avoid expanding type synonyms
during pretty printing. Hence, Type
has a variant
NoteTy TyNote Type
, where
data TyNote = FTVNote TyVarSet -- The free type variables of the noted expression | SynNote Type -- Used for type synonyms -- The Type is always a TyConApp, and is the un-expanded form. -- The type to which the note is attached is the expanded form.
In other words, a NoteTy
represents the expanded form of a
type synonym together with a note stating its source form.
During translation from HsType
to Type
the
function Type.mkSynTy
is used to construct representations
of applications of type synonyms. It creates a NoteTy
node
if the synonym is applied to a sufficient number of arguments;
otherwise, it builds a simple TyConApp
and leaves it to
TcMType.checkValidType
to pick up invalid unsaturated
synonym applications. While creating a NoteTy
,
mkSynTy
also expands the synonym by substituting the type
arguments for the parameters of the synonym definition, using
Type.substTyWith
.
The function mkSynTy
is used indirectly via
mkGenTyConApp
, mkAppTy
, and
mkAppTy
, which construct type representations involving
type applications. The function mkSynTy
is also used
directly during type checking interface files; this is for tedious
reasons to do with forall hoisting - see the comment at
TcIface.mkIfTcApp
.
Data types declared by a newtype
declarations constitute new
type constructors---i.e., they are not just type macros, but introduce
new type names. However, provided that a newtype is not recursive, we
still want to implement it by its representation type. GHC realises this
by providing two flavours of type equality: (1) tcEqType
is
source-level type equality, which compares newtypes and
PredType
s by name, and (2) coreEqType
compares
them structurally (by using deepCoreView
to expand the
representation before comparing). The function
deepCoreView
(via coreView
) invokes
expandNewTcApp
for every type constructor application
(TyConApp
) to determine whether we are looking at a newtype
application that needs to be expanded to its representation type.
The dictionary translation of type classes, translates each predicate in
a type context of a type signature into an additional argument, which
carries a dictionary with the functions overloaded by the corresponding
class. The Type
data type has a special variant
PredTy PredType
for predicates, where
data PredType = ClassP Class [Type] -- Class predicate | IParam (IPName Name) Type -- Implicit parameter
These types need to be handled as source type during type checking, but
turn into their representations when inspected through
coreView
. The representation is determined by
Type.predTypeRep
.
Type constructor applications are represented in Type
by
the variant TyConApp :: TyCon -> [Type] -> Type
. The first
argument to TyConApp
, namely TyCon.TyCon
,
distinguishes between function type constructors (variant
FunTyCon
) and algebraic type constructors (variant
AlgTyCon
), which arise from data and newtype declarations.
The variant AlgTyCon
contains all the information available
from the data/newtype declaration as well as derived information, such
as the Unique
and argument variance information. This
includes a field algTcRhs :: AlgTyConRhs
, where
AlgTyConRhs
distinguishes three kinds of algebraic data
type declarations: (1) declarations that have been exported abstractly,
(2) data
declarations, and (3) newtype
declarations. The last two both include their original right hand side;
in addition, the third variant also caches the "ultimate" representation
type, which is the right hand side after expanding all type synonyms and
non-recursive newtypes.
Both data and newtype declarations refer to their data constructors
represented as DataCon.DataCon
, which include all details
of their signature (as derived from the original declaration) as well
information for code generation, such as their tag value.
Class declarations turn into values of type Class.Class
.
They represent methods as the Id
s of the dictionary
selector functions. Similar selector functions are available for
superclass dictionaries.
Instance declarations turn into values of type
InstEnv.Instance
, which in interface files are represented
as IfaceSyn.IfaceInst
. Moreover, the type
InstEnv.InstEnv
, which is a synonym for UniqFM
ClsInstEnv
, provides a mapping of classes to their
instances---ClsInstEnv
is essentially a list of instance
declarations.
Last modified: Sun Jun 19 13:07:22 EST 2005