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

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Exp.Annot.Compounds

Contents

Description

Utilities for constructing and destructing compound expressions.

For the annotated version of the AST.

Synopsis

Documentation

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.