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

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Exp.Generic.Exp

Description

Generic expression representation.

Synopsis

Documentation

type family GAnnot l Source

Type functions associated with a language definition.

These produce the types used for annotations, bindings, bound occurrences and primitives for that language.

type family GBind l Source

type family GBound l Source

type family GPrim l Source

data GExp l Source

Generic expression representation.

Constructors

XAnnot !(GAnnot l) !(GExp l)

An annotated expression.

XPrim !(GPrim l)

Primitive operator or literal.

XCon !(DaCon l)

Data constructor.

XVar !(GBound l)

Value or Witness variable (level-0).

XAbs !(GAbs l) !(GExp l)

Function abstraction.

XApp !(GExp l) !(GArg l)

Function application.

XLet !(GLets l) !(GExp l)

Possibly recursive bindings.

XCase !(GExp l) ![GAlt l]

Case branching.

XCast !(GCast l) !(GExp l)

Type casting.

data GAbs l Source

Abstractions.

This indicates what sort of object is being abstracted over in an XAbs.

Constructors

ALAM !(GBind l)

Level-1 abstraction (spec)

ALam !(GBind l)

Level-0 abstraction (value and witness)

Instances

pattern XLAM :: GBind t -> GExp t -> GExp t Source

pattern XLam :: GBind t -> GExp t -> GExp t Source

data GArg l Source

Arguments.

Carries an argument that can be supplied to a function.

Constructors

RType !(Type l)

Type argument.

RExp !(GExp l)

Value argument.

RWitness !(GWitness l)

Witness argument.

data GLets l Source

Possibly recursive bindings.

Constructors

LLet !(GBind l) !(GExp l)

Non-recursive binding.

LRec ![(GBind l, GExp l)]

Recursive binding.

LPrivate ![GBind l] !(Maybe (Type l)) ![GBind l]

Introduce a private region variable and witnesses to its properties.

data GAlt l Source

Case alternatives.

Constructors

AAlt !(GPat l) !(GExp l) 

data GPat l Source

Patterns.

Constructors

PDefault

The default pattern always succeeds.

PData !(DaCon l) ![GBind l]

Match a data constructor and bind its arguments.

Instances

data GCast l Source

Type casts.

Constructors

CastWeakenEffect !(Type l)

Weaken the effect of an expression.

CastPurify !(GWitness l)

Purify the effect of an expression.

CastBox

Box up a computation, suspending its evaluation and capturing its effects in the S computaiton type.

CastRun

Run a computation, releasing its effects into the context.

Instances

data GWitness l Source

Witnesses.

Constructors

WVar !(GBound l)

Witness variable.

WCon !(GWiCon l)

Witness constructor.

WApp !(GWitness l) !(GWitness l)

Witness application.

WType !(Type l)

Type can appear as an argument of a witness application.

Instances

data GWiCon l Source

Witness constructors.

Constructors

WiConBound !(GBound l) !(Type l)

Witness constructors defined in the environment. In the interpreter we use this to hold runtime capabilities. The attached type must be closed.

Instances

type ShowLanguage l = (Show l, Show (GAnnot l), Show (GBind l), Show (GBound l), Show (GPrim l)) Source

Synonym for Show constraints of all language types.