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

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Exp.Annot

Contents

Synopsis

Abstract Syntax

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 !a !(Type n)

Type can appear as the argument of an application.

XWitness !a !(Witness a n)

Witness can appear as the argument of an application.

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.

LPrivate ![Bind n] !(Maybe (Type n)) ![Bind n]

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

data Alt a n Source

Case alternatives.

Constructors

AAlt !(Pat n) !(Exp 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 Source 
Eq n => Eq (Pat n) Source 
Show n => Show (Pat n) Source 
NFData n => NFData (Pat n) Source 

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.

CastPurify !(Witness a n)

Purify the effect (action) of an expression.

CastBox

Box up a computation, capturing its effects in the S computation type.

CastRun

Run a computation, releasing its effects into the environment.

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.

WType a !(Type n)

Type can appear as the argument of an application.

Data Constructors

data DaCon n Source

Data constructors.

Constructors

DaConUnit

Baked in unit data constructor.

DaConPrim

Primitive data constructor used for literals and baked-in constructors.

The type of the constructor needs to be attached to handle the case where there are too many constructors in the data type to list, like for Int literals. In this case we determine what data type it belongs to from the attached type of the data constructor.

Fields

daConName :: !n

Name of the data constructor.

daConType :: !(Type n)

Type of the data constructor.

DaConBound

Data constructor that has a data type declaration.

Fields

daConName :: !n

Name of the data constructor.

Instances

Witness Constructors

data WiCon n Source

Witness constructors.

Constructors

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

Predicates

Atoms

isXVar :: Exp a n -> Bool Source

Check whether an expression is a variable.

isXCon :: Exp a n -> Bool Source

Check whether an expression is a constructor.

isAtomX :: Exp a n -> Bool Source

Check whether an expression is a XVar or an XCon, or some type or witness atom.

isAtomW :: Witness a n -> Bool Source

Check whether a witness is a WVar or WCon.

Lambdas

isXLAM :: Exp a n -> Bool Source

Check whether an expression is a spec abstraction (level-1).

isXLam :: Exp a n -> Bool Source

Check whether an expression is a value or witness abstraction (level-0).

isLambdaX :: Exp a n -> Bool Source

Check whether an expression is a spec, value, or witness abstraction.

Applications

isXApp :: Exp a n -> Bool Source

Check whether an expression is an XApp.

Cast

isXCast :: Exp a n -> Bool Source

Check whether this is a cast expression.

isXCastBox :: Exp a n -> Bool Source

Check whether this is a box cast.

isXCastRun :: Exp a n -> Bool Source

Check whether this is a run cast.

Let bindings

isXLet :: Exp a n -> Bool Source

Check whether an expression is a XLet.

Patterns

isPDefault :: Pat n -> Bool Source

Check whether an alternative is a PDefault.

Types and Witnesses

isXType :: Exp a n -> Bool Source

Check whether an expression is an XType.

isXWitness :: Exp a n -> Bool Source

Check whether an expression is an XWitness.

Compounds

Annotations

annotOfExp :: Exp a n -> a Source

Take the outermost annotation from an expression.

mapAnnotOfExp :: (a -> a) -> Exp a n -> Exp a n Source

Apply a function to the annotation of an expression.

Lambdas

xLAMs :: a -> [Bind n] -> Exp a n -> Exp a n Source

Make some nested type lambdas.

xLams :: a -> [Bind n] -> Exp a n -> Exp a n Source

Make some nested value or witness lambdas.

makeXLamFlags :: a -> [(Bool, Bind n)] -> Exp a n -> Exp a n Source

Make some nested lambda abstractions, using a flag to indicate whether the lambda is a level-1 (True), or level-0 (False) binder.

takeXLAMs :: Exp a n -> Maybe ([Bind n], Exp a n) Source

Split type lambdas from the front of an expression, or Nothing if there aren't any.

takeXLams :: Exp a n -> Maybe ([Bind n], Exp a n) Source

Split nested value or witness lambdas from the front of an expression, or Nothing if there aren't any.

takeXLamFlags :: Exp a n -> Maybe ([(Bool, Bind n)], Exp a n) Source

Split nested lambdas from the front of an expression, with a flag indicating whether the lambda was a level-1 (True), or level-0 (False) binder.

data Param n Source

Parameters of a function.

Constructors

ParamType (Bind n) 
ParamValue (Bind n) 
ParamBox 

Instances

Show n => Show (Param n) Source 

takeXLamParam :: Exp a n -> Maybe ([Param n], Exp a n) Source

Take the parameters of a function.

Applications

xApps :: a -> Exp a n -> [Exp a n] -> Exp a n Source

Build sequence of value applications.

makeXAppsWithAnnots :: Exp a n -> [(Exp a n, a)] -> Exp a n Source

Build sequence of applications. Similar to xApps but also takes list of annotations for the XApp constructors.

takeXApps :: Exp a n -> Maybe (Exp a n, [Exp a n]) Source

Flatten an application into the function part and its arguments.

Returns Nothing if there is no outer application.

takeXApps1 :: Exp a n -> Exp a n -> (Exp a n, [Exp a n]) Source

Flatten an application into the function part and its arguments.

This is like takeXApps above, except we know there is at least one argument.

takeXAppsAsList :: Exp a n -> [Exp a n] Source

Flatten an application into the function parts and arguments, if any.

takeXAppsWithAnnots :: Exp a n -> (Exp a n, [(Exp a n, a)]) Source

Destruct sequence of applications. Similar to takeXAppsAsList but also keeps annotations for later.

takeXConApps :: Exp a n -> Maybe (DaCon n, [Exp a n]) Source

Flatten an application of a data constructor into the constructor and its arguments.

Returns Nothing if the expression isn't a constructor application.

takeXPrimApps :: Exp a n -> Maybe (n, [Exp a n]) Source

Flatten an application of a primop into the variable and its arguments.

Returns Nothing if the expression isn't a primop application.

Lets

xLets :: a -> [Lets a n] -> Exp a n -> Exp a n Source

Wrap some let-bindings around an expression.

xLetsAnnot :: [(Lets a n, a)] -> Exp a n -> Exp a n Source

Wrap some let-bindings around an expression, with individual annotations.

splitXLets :: Exp a n -> ([Lets a n], Exp a n) Source

Split let-bindings from the front of an expression, if any.

splitXLetsAnnot :: Exp a n -> ([(Lets a n, a)], Exp a n) Source

Split let-bindings from the front of an expression, with annotations.

bindsOfLets :: Lets a n -> ([Bind n], [Bind n]) Source

Take the binds of a Lets.

The level-1 and level-0 binders are returned separately.

specBindsOfLets :: Lets a n -> [Bind n] Source

Like bindsOfLets but only take the spec (level-1) binders.

valwitBindsOfLets :: Lets a n -> [Bind n] Source

Like bindsOfLets but only take the value and witness (level-0) binders.

Alternatives

patOfAlt :: Alt a n -> Pat n Source

Take the pattern of an alternative.

takeCtorNameOfAlt :: Alt a n -> Maybe n Source

Take the constructor name of an alternative, if there is one.

Patterns

bindsOfPat :: Pat n -> [Bind n] Source

Take the binds of a Pat.

Casts

makeRuns :: a -> Int -> Exp a n -> Exp a n Source

Wrap an expression in the given number of run casts.

Witnesses

wApp :: a -> Witness a n -> Witness a n -> Witness a n Source

Construct a witness application

wApps :: a -> Witness a n -> [Witness a n] -> Witness a n Source

Construct a sequence of witness applications

annotOfWitness :: Witness a n -> a Source

Take the annotation from a witness.

takeXWitness :: Exp a n -> Maybe (Witness a n) Source

Take the witness from an XWitness argument, if any.

takeWAppsAsList :: Witness a n -> [Witness a n] Source

Flatten an application into the function parts and arguments, if any.

takePrimWiConApps :: Witness a n -> Maybe (n, [Witness a n]) Source

Flatten an application of a witness into the witness constructor name and its arguments.

Returns nothing if there is no witness constructor in head position.

Types

takeXType :: Exp a n -> Maybe (Type n) Source

Take the type from an XType argument, if any.

Data Constructors

xUnit :: a -> Exp a n Source

Construct a value of unit type.

dcUnit :: DaCon n Source

The unit data constructor.

takeNameOfDaCon :: DaCon n -> Maybe n Source

Take the name of data constructor, if there is one.

takeTypeOfDaCon :: DaCon n -> Maybe (Type n) Source

Take the type annotation of a data constructor, if we know it locally.