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

Safe HaskellSafe-Inferred

DDC.Core.Exp.Annot

Contents

Description

Core language AST that includes an annotation on every node of an expression.

This is the default representation for Disciple Core, and should be preferred over the Simple version of the AST in most cases.

  • Local transformations on this AST should propagate the annotations in a way that would make sense if they were source position identifiers that tracked the provenance of each code snippet. If the specific annotations attached to the AST would not make sense after such a transformation, then the client should erase them to () beforehand using the reannotate transform.
  • Global transformations that drastically change the provenance of code snippets should accept an AST with an arbitrary annotation type, but produce one with the annotations set to ().

Synopsis

Documentation

Expressions

data Exp a n Source

Well-typed expressions have types of kind Data.

Constructors

XVar !a !(Bound n)

Value variable or primitive operation.

XCon !a !(DaCon n)

Data constructor or literal.

XLAM !a !(Bind n) !(Exp a n)

Type abstraction (level-1).

XLam !a !(Bind n) !(Exp a n)

Value and Witness abstraction (level-0).

XApp !a !(Exp a n) !(Exp a n)

Application.

XLet !a !(Lets a n) !(Exp a n)

Possibly recursive bindings.

XCase !a !(Exp a n) ![Alt a n]

Case branching.

XCast !a !(Cast a n) !(Exp a n)

Type cast.

XType !(Type n)

Type can appear as the argument of an application.

XWitness !(Witness a n)

Witness can appear as the argument of an application.

Instances

Reannotate Exp 
Complies Exp 
SubstituteWX Exp 
SubstituteXX Exp 
Annotate Exp Exp 
Deannotate Exp Exp 
BindStruct (Exp a) 
SpreadX (Exp a) 
SupportX (Exp a) 
SubstituteTX (Exp a) 
MapBoundX (Exp a) n 
Ord n => MapBoundT (Exp a) n 
(Eq a, Eq n) => Eq (Exp a n) 
(Show a, Show n) => Show (Exp a n) 
(Pretty n, Eq n) => Pretty (Exp a n) 
(NFData a, NFData n) => NFData (Exp a n) 

data Lets a n Source

Possibly recursive bindings.

Constructors

LLet !(Bind n) !(Exp a n)

Non-recursive expression binding.

LRec ![(Bind n, Exp a n)]

Recursive binding of lambda abstractions.

LLetRegions ![Bind n] ![Bind n]

Bind a local region variable, and witnesses to its properties.

LWithRegion !(Bound n)

Holds a region handle during evaluation.

Instances

Reannotate Lets 
Annotate Lets Lets 
Deannotate Lets Lets 
SpreadX (Lets a) 
SupportX (Lets a) 
(Eq a, Eq n) => Eq (Lets a n) 
(Show a, Show n) => Show (Lets a n) 
(Pretty n, Eq n) => Pretty (Lets a n) 
(NFData a, NFData n) => NFData (Lets a n) 

data Alt a n Source

Case alternatives.

Constructors

AAlt !(Pat n) !(Exp a n) 

Instances

Reannotate Alt 
Complies Alt 
SubstituteWX Alt 
SubstituteXX Alt 
Annotate Alt Alt 
Deannotate Alt Alt 
BindStruct (Alt a) 
SpreadX (Alt a) 
SupportX (Alt a) 
SubstituteTX (Alt a) 
MapBoundX (Alt a) n 
Ord n => MapBoundT (Alt a) n 
(Eq a, Eq n) => Eq (Alt a n) 
(Show a, Show n) => Show (Alt a n) 
(Pretty n, Eq n) => Pretty (Alt a n) 
(NFData a, NFData n) => NFData (Alt a n) 

data Pat n Source

Pattern matching.

Constructors

PDefault

The default pattern always succeeds.

PData !(DaCon n) ![Bind n]

Match a data constructor and bind its arguments.

Instances

SpreadX Pat 
Eq n => Eq (Pat n) 
Show n => Show (Pat n) 
(Pretty n, Eq n) => Pretty (Pat n) 
NFData n => NFData (Pat n) 

data Cast a n Source

Type casts.

Constructors

CastWeakenEffect !(Effect n)

Weaken the effect of an expression. The given effect is added to the effect of the body.

CastWeakenClosure ![Exp a n]

Weaken the closure of an expression. The closures of these expressions are added to the closure of the body.

CastPurify !(Witness a n)

Purify the effect (action) of an expression.

CastForget !(Witness a n)

Forget about the closure (sharing) of an expression.

CastSuspend

Suspend a computation, capturing its effects in the S computation type.

CastRun

Run a computation, releasing its effects into the environment.

Instances

Reannotate Cast 
SubstituteWX Cast 
SubstituteXX Cast 
Annotate Cast Cast 
Deannotate Cast Cast 
BindStruct (Cast a) 
SpreadX (Cast a) 
SupportX (Cast a) 
SubstituteTX (Cast a) 
MapBoundX (Cast a) n 
Ord n => MapBoundT (Cast a) n 
(Eq a, Eq n) => Eq (Cast a n) 
(Show a, Show n) => Show (Cast a n) 
(Pretty n, Eq n) => Pretty (Cast a n) 
(NFData a, NFData n) => NFData (Cast a n) 

Witnesses

data Witness a n Source

When a witness exists in the program it guarantees that a certain property of the program is true.

Constructors

WVar a !(Bound n)

Witness variable.

WCon a !(WiCon n)

Witness constructor.

WApp a !(Witness a n) !(Witness a n)

Witness application.

WJoin a !(Witness a n) !(Witness a n)

Joining of witnesses.

WType a !(Type n)

Type can appear as the argument of an application.

Data Constructors

data DaCon n Source

Data constructors.

Constructors

DaCon 

Fields

daConName :: !(DaConName n)

Name of the data constructor.

daConType :: !(Type n)

Type of the data constructor. The type must be closed.

daConIsAlgebraic :: !Bool

Algebraic constructors can be deconstructed with case-expressions, and must have a data type declaration.

Non-algebraic types like Float can't be inspected with case-expressions.

Instances

SpreadX DaCon 
Eq n => Eq (DaCon n) 
Show n => Show (DaCon n) 
(Pretty n, Eq n) => Pretty (DaCon n) 
NFData n => NFData (DaCon n) 

data DaConName n Source

Data constructor names.

Constructors

DaConUnit

The unit data constructor is builtin.

DaConNamed n

Data constructor name defined by the client.

Instances

Eq n => Eq (DaConName n) 
Show n => Show (DaConName n) 
NFData n => NFData (DaConName n) 

Witness Constructors

data WiCon n Source

Witness constructors.

Constructors

WiConBuiltin !WbCon

Witness constructors baked into the language.

WiConBound !(Bound n) !(Type n)

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

Instances

SpreadX WiCon 
Eq n => Eq (WiCon n) 
Show n => Show (WiCon n) 
(Pretty n, Eq n) => Pretty (WiCon n) 
NFData n => NFData (WiCon n) 

data WbCon Source

Built-in witness constructors.

These are used to convert a runtime capability into a witness that the corresponding property is true.

Constructors

WbConPure

(axiom) The pure effect is pure.

pure     :: Pure !0
WbConEmpty

(axiom) The empty closure is empty.

empty    :: Empty $0
WbConUse

Convert a capability guaranteeing that a region is in the global heap, into a witness that a closure using this region is empty. This lets us rely on the garbage collector to reclaim objects in the region. It is needed when we suspend the evaluation of expressions that have a region in their closure, because the type of the returned thunk may not reveal that it references objects in that region.

use      :: [r : %]. Global r => Empty (Use r)
WbConRead

Convert a capability guaranteeing the constancy of a region, into a witness that a read from that region is pure. This lets us suspend applications that read constant objects, because it doesn't matter if the read is delayed, we'll always get the same result.

read     :: [r : %]. Const r  => Pure (Read r)
WbConAlloc

Convert a capability guaranteeing the constancy of a region, into a witness that allocation into that region is pure. This lets us increase the sharing of constant objects, because we can't tell constant objects of the same value apart.

alloc    :: [r : %]. Const r  => Pure (Alloc r)