ddc-core-0.4.3.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 (Type 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.

Instances

Reannotate Exp Source # 

Methods

reannotate :: (a -> b) -> Exp a n -> Exp b n Source #

reannotateM :: Monad m => (a -> m b) -> Exp a n -> m (Exp b n) Source #

Complies Exp Source # 

Methods

compliesX :: (Ord n, Show n) => Profile n -> Env n -> Env n -> Context -> Exp a n -> CheckM a n (Set n, Set n)

SubstituteWX Exp Source # 

Methods

substituteWithWX :: Ord n => Witness a n -> Sub n -> Exp a n -> Exp a n Source #

SubstituteXX Exp Source # 

Methods

substituteWithXX :: Ord n => Exp a n -> Sub n -> Exp a n -> Exp a n Source #

SpreadX (Exp a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Exp a n -> Exp a n Source #

SupportX (Exp a) Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Exp a n -> Support n Source #

SubstituteTX (Exp a) Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Exp a n -> Exp a n Source #

MapBoundX (Exp a) n Source # 

Methods

mapBoundAtDepthX :: (Int -> Bound n -> Bound n) -> Int -> Exp a n -> Exp a n Source #

(Eq a, Eq n) => Eq (Exp a n) Source # 

Methods

(==) :: Exp a n -> Exp a n -> Bool #

(/=) :: Exp a n -> Exp a n -> Bool #

(Show a, Show n) => Show (Exp a n) Source # 

Methods

showsPrec :: Int -> Exp a n -> ShowS #

show :: Exp a n -> String #

showList :: [Exp a n] -> ShowS #

(NFData a, NFData n) => NFData (Exp a n) Source # 

Methods

rnf :: Exp a n -> () #

data PrettyMode (Exp a n) Source # 

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.

Instances

Reannotate Lets Source # 

Methods

reannotate :: (a -> b) -> Lets a n -> Lets b n Source #

reannotateM :: Monad m => (a -> m b) -> Lets a n -> m (Lets b n) Source #

SpreadX (Lets a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Lets a n -> Lets a n Source #

SupportX (Lets a) Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Lets a n -> Support n Source #

(Eq a, Eq n) => Eq (Lets a n) Source # 

Methods

(==) :: Lets a n -> Lets a n -> Bool #

(/=) :: Lets a n -> Lets a n -> Bool #

(Show a, Show n) => Show (Lets a n) Source # 

Methods

showsPrec :: Int -> Lets a n -> ShowS #

show :: Lets a n -> String #

showList :: [Lets a n] -> ShowS #

(NFData a, NFData n) => NFData (Lets a n) Source # 

Methods

rnf :: Lets a n -> () #

data PrettyMode (Lets a n) Source # 

data Alt a n Source #

Case alternatives.

Constructors

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

Instances

Reannotate Alt Source # 

Methods

reannotate :: (a -> b) -> Alt a n -> Alt b n Source #

reannotateM :: Monad m => (a -> m b) -> Alt a n -> m (Alt b n) Source #

Complies Alt Source # 

Methods

compliesX :: (Ord n, Show n) => Profile n -> Env n -> Env n -> Context -> Alt a n -> CheckM a n (Set n, Set n)

SubstituteWX Alt Source # 

Methods

substituteWithWX :: Ord n => Witness a n -> Sub n -> Alt a n -> Alt a n Source #

SubstituteXX Alt Source # 

Methods

substituteWithXX :: Ord n => Exp a n -> Sub n -> Alt a n -> Alt a n Source #

SpreadX (Alt a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Alt a n -> Alt a n Source #

SupportX (Alt a) Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Alt a n -> Support n Source #

SubstituteTX (Alt a) Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Alt a n -> Alt a n Source #

MapBoundX (Alt a) n Source # 

Methods

mapBoundAtDepthX :: (Int -> Bound n -> Bound n) -> Int -> Alt a n -> Alt a n Source #

(Eq a, Eq n) => Eq (Alt a n) Source # 

Methods

(==) :: Alt a n -> Alt a n -> Bool #

(/=) :: Alt a n -> Alt a n -> Bool #

(Show a, Show n) => Show (Alt a n) Source # 

Methods

showsPrec :: Int -> Alt a n -> ShowS #

show :: Alt a n -> String #

showList :: [Alt a n] -> ShowS #

(NFData a, NFData n) => NFData (Alt a n) Source # 

Methods

rnf :: Alt a n -> () #

data PrettyMode (Alt a n) Source # 

data Pat n Source #

Pattern matching.

Constructors

PDefault

The default pattern always succeeds.

PData !(DaCon n (Type n)) ![Bind n]

Match a data constructor and bind its arguments.

Instances

SpreadX Pat Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Pat n -> Pat n Source #

Eq n => Eq (Pat n) Source # 

Methods

(==) :: Pat n -> Pat n -> Bool #

(/=) :: Pat n -> Pat n -> Bool #

Show n => Show (Pat n) Source # 

Methods

showsPrec :: Int -> Pat n -> ShowS #

show :: Pat n -> String #

showList :: [Pat n] -> ShowS #

NFData n => NFData (Pat n) Source # 

Methods

rnf :: 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.

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.

Instances

Reannotate Cast Source # 

Methods

reannotate :: (a -> b) -> Cast a n -> Cast b n Source #

reannotateM :: Monad m => (a -> m b) -> Cast a n -> m (Cast b n) Source #

SubstituteWX Cast Source # 

Methods

substituteWithWX :: Ord n => Witness a n -> Sub n -> Cast a n -> Cast a n Source #

SubstituteXX Cast Source # 

Methods

substituteWithXX :: Ord n => Exp a n -> Sub n -> Cast a n -> Cast a n Source #

SpreadX (Cast a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Cast a n -> Cast a n Source #

SupportX (Cast a) Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Cast a n -> Support n Source #

SubstituteTX (Cast a) Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Cast a n -> Cast a n Source #

MapBoundX (Cast a) n Source # 

Methods

mapBoundAtDepthX :: (Int -> Bound n -> Bound n) -> Int -> Cast a n -> Cast a n Source #

(Eq a, Eq n) => Eq (Cast a n) Source # 

Methods

(==) :: Cast a n -> Cast a n -> Bool #

(/=) :: Cast a n -> Cast a n -> Bool #

(Show a, Show n) => Show (Cast a n) Source # 

Methods

showsPrec :: Int -> Cast a n -> ShowS #

show :: Cast a n -> String #

showList :: [Cast a n] -> ShowS #

(NFData a, NFData n) => NFData (Cast a n) Source # 

Methods

rnf :: 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.

WType a !(Type n)

Type can appear as the argument of an application.

Instances

Reannotate Witness Source # 

Methods

reannotate :: (a -> b) -> Witness a n -> Witness b n Source #

reannotateM :: Monad m => (a -> m b) -> Witness a n -> m (Witness b n) Source #

SubstituteWX Witness Source # 

Methods

substituteWithWX :: Ord n => Witness a n -> Sub n -> Witness a n -> Witness a n Source #

SpreadX (Witness a) Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> Witness a n -> Witness a n Source #

SupportX (Witness a) Source # 

Methods

support :: Ord n => KindEnv n -> TypeEnv n -> Witness a n -> Support n Source #

SubstituteTX (Witness a) Source # 

Methods

substituteWithTX :: Ord n => Type n -> Sub n -> Witness a n -> Witness a n Source #

MapBoundX (Witness a) n Source # 

Methods

mapBoundAtDepthX :: (Int -> Bound n -> Bound n) -> Int -> Witness a n -> Witness a n Source #

(Eq a, Eq n) => Eq (Witness a n) Source # 

Methods

(==) :: Witness a n -> Witness a n -> Bool #

(/=) :: Witness a n -> Witness a n -> Bool #

(Show a, Show n) => Show (Witness a n) Source # 

Methods

showsPrec :: Int -> Witness a n -> ShowS #

show :: Witness a n -> String #

showList :: [Witness a n] -> ShowS #

(NFData a, NFData n) => NFData (Witness a n) Source # 

Methods

rnf :: Witness a n -> () #

Data Constructors

data DaCon n t 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

DaConBound

Data constructor that has a data type declaration.

Fields

Instances

(Eq n, Eq t) => Eq (DaCon n t) Source # 

Methods

(==) :: DaCon n t -> DaCon n t -> Bool #

(/=) :: DaCon n t -> DaCon n t -> Bool #

(Show n, Show t) => Show (DaCon n t) Source # 

Methods

showsPrec :: Int -> DaCon n t -> ShowS #

show :: DaCon n t -> String #

showList :: [DaCon n t] -> ShowS #

(NFData n, NFData t) => NFData (DaCon n t) Source # 

Methods

rnf :: DaCon n t -> () #

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

SpreadX WiCon Source # 

Methods

spreadX :: Ord n => Env n -> Env n -> WiCon n -> WiCon n Source #

Eq n => Eq (WiCon n) Source # 

Methods

(==) :: WiCon n -> WiCon n -> Bool #

(/=) :: WiCon n -> WiCon n -> Bool #

Show n => Show (WiCon n) Source # 

Methods

showsPrec :: Int -> WiCon n -> ShowS #

show :: WiCon n -> String #

showList :: [WiCon n] -> ShowS #

NFData n => NFData (WiCon n) Source # 

Methods

rnf :: WiCon n -> () #

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 # 

Methods

showsPrec :: Int -> Param n -> ShowS #

show :: Param n -> String #

showList :: [Param n] -> ShowS #

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 (Type 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 t Source #

The unit data constructor.

takeNameOfDaCon :: DaCon n t -> Maybe n Source #

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

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

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