ddc-core-0.4.3.1: Disciplined Disciple Compiler core language and type checker.

Safe HaskellSafe
LanguageHaskell98

DDC.Type.Exp.Generic.Exp

Contents

Synopsis

Type Families

type family GTAnnot l Source #

Yield the type of annotations.

Instances

type GTAnnot Flat Source # 
type GTAnnot Flat = ()

type family GTBindVar l Source #

Yield the type of binding occurrences of variables.

Instances

type GTBindVar Flat Source # 
type GTBindVar Flat = Text

type family GTBoundVar l Source #

Yield the type of bound occurrences of variables.

Instances

type GTBoundVar Flat Source # 
type GTBoundVar Flat = Text

type family GTBindCon l Source #

Yield the type of binding occurrences of constructors.

Instances

type GTBindCon Flat Source # 
type GTBindCon Flat = Text

type family GTBoundCon l Source #

Yield the type of bound occurrences of constructors.

Instances

type GTBoundCon Flat Source # 
type GTBoundCon Flat = Text

type family GTPrim l Source #

Yield the type of primitive type names.

Instances

type GTPrim Flat Source # 
type GTPrim Flat = Text

Abstract Syntax

data GType l Source #

Generic type expression representation.

Constructors

TAnnot !(GTAnnot l) (GType l)

An annotated type.

TCon !(GTyCon l)

Type constructor or literal.

TVar !(GTBoundVar l)

Type variable.

TAbs !(GTBindVar l) (GType l) (GType l)

Type abstracton.

TApp !(GType l) (GType l)

Type application.

Instances

(Eq (GTAnnot l), Eq (GTyCon l), Eq (GTBindVar l), Eq (GTBoundVar l)) => Eq (GType l) Source # 

Methods

(==) :: GType l -> GType l -> Bool #

(/=) :: GType l -> GType l -> Bool #

ShowGType l => Show (GType l) Source # 

Methods

showsPrec :: Int -> GType l -> ShowS #

show :: GType l -> String #

showList :: [GType l] -> ShowS #

data GTyCon l Source #

Wrapper for primitive constructors that adds the ones common to SystemFω based languages.

Constructors

TyConVoid

The void constructor.

TyConUnit

The unit constructor.

TyConFun

The function constructor.

TyConUnion !(GType l)

Take the least upper bound at the given kind.

TyConBot !(GType l)

The least element of the given kind.

TyConForall !(GType l)

The universal quantifier with a parameter of the given kind.

TyConExists !(GType l)

The existential quantifier with a parameter of the given kind.

TyConPrim !(GTPrim l)

Primitive constructor.

TyConBound !(GTBoundCon l)

Bound constructor.

Instances

(Eq (GType l), Eq (GTPrim l), Eq (GTBoundCon l)) => Eq (GTyCon l) Source # 

Methods

(==) :: GTyCon l -> GTyCon l -> Bool #

(/=) :: GTyCon l -> GTyCon l -> Bool #

ShowGType l => Show (GTyCon l) Source # 

Methods

showsPrec :: Int -> GTyCon l -> ShowS #

show :: GTyCon l -> String #

showList :: [GTyCon l] -> ShowS #

Syntactic Sugar

pattern TApp2 :: forall t. GType t -> GType t -> GType t -> GType t Source #

Applcation of a type to two arguments.

pattern TApp3 :: forall t. GType t -> GType t -> GType t -> GType t -> GType t Source #

Applcation of a type to three arguments.

pattern TApp4 :: forall t. GType t -> GType t -> GType t -> GType t -> GType t -> GType t Source #

Applcation of a type to four arguments.

pattern TApp5 :: forall t. GType t -> GType t -> GType t -> GType t -> GType t -> GType t -> GType t Source #

Applcation of a type to five arguments.

pattern TVoid :: forall t. GType t Source #

Representation of the void type.

pattern TUnit :: forall t. GType t Source #

Representation of the unit type.

pattern TFun :: forall t. GType t -> GType t -> GType t Source #

Representation of the function type.

pattern TBot :: forall t. GType t -> GType t Source #

Representation of the bottom type at a given kind.

pattern TUnion :: forall t. GType t -> GType t -> GType t -> GType t Source #

Representation of a union of two types.

pattern TPrim :: forall t. GTPrim t -> GType t Source #

Representation of primitive type constructors.

Classes

type ShowGType l = (Show l, Show (GTAnnot l), Show (GTBindVar l), Show (GTBoundVar l), Show (GTBindCon l), Show (GTBoundCon l), Show (GTPrim l)) Source #

Synonym for show constraints of all language types.