ddc-core-flow-0.4.3.1: Disciplined Disciple Compiler data flow compiler.

Safe HaskellSafe
LanguageHaskell98

DDC.Core.Flow.Compounds

Contents

Description

Short-hands for constructing compound expressions.

Synopsis

Documentation

Lambdas

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

Make some nested type lambdas.

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

Make some nested value or witness lambdas.

makeXLamFlags :: [(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.

Applications

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

Build sequence of value applications.

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.

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 :: [Lets a n] -> Exp a n -> Exp a n Source #

Wrap some let-bindings around an expression.

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

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

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.

Patterns

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

Take the binds of a Pat.

Alternatives

takeCtorNameOfAlt :: Alt a n -> Maybe n Source #

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

Witnesses

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

Construct a witness application

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

Construct a sequence of witness applications

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 :: Exp a n Source #

Construct a value of unit type.

dcUnit :: DaCon n t #

The unit data constructor.

takeNameOfDaCon :: DaCon n t -> Maybe n #

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

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

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

Fragment specific kinds

Fragment specific types

isRateNatType :: Type Name -> Bool Source #

Check if some type is a fully applied type of a RateNat

isSeriesType :: Type Name -> Bool Source #

Check if some type is a fully applied type of a Series.

isRateVecType :: Type Name -> Bool Source #

Check if some type is a fully applied type of a RateVec.

isRefType :: Type Name -> Bool Source #

Check if some type is a fully applied type of a Ref.

isVectorType :: Type Name -> Bool Source #

Check if some type is a fully applied type of a Vector.

isProcessType :: Type Name -> Bool Source #

Check if some type is a fully applied Process.

Primtiive types

tVoid :: Type Name Source #

Primitive `Void#` type.

tBool :: Type Name Source #

Primitive `Bool#` type.

tNat :: Type Name Source #

Primitive Nat# type.

tInt :: Type Name Source #

Primitive `Int#` type.

tWord :: Int -> Type Name Source #

Primitive `WordN#` type of the given width.

tFloat :: Int -> Type Name Source #

Primitive `FloatN#` type of the given width.

tVec :: Int -> Type Name -> Type Name Source #

Primitive VecN# a.

Primitive literals and data constructors

xBool :: Bool -> Exp a Name Source #

A literal Bool#

dcBool :: Bool -> DaCon Name (Type Name) Source #

A literal Bool# data constructor.

xNat :: Integer -> Exp a Name Source #

A literal Nat#

dcNat :: Integer -> DaCon Name (Type Name) Source #

A Literal Nat# data constructor.

dcTuple1 :: DaCon Name (Type Name) Source #

Data constructor for Tuple1#

xTuple2 :: Type Name -> Type Name -> Exp a Name -> Exp a Name -> Exp a Name Source #

Construct a Tuple2#

dcTuple2 :: DaCon Name (Type Name) Source #

Data constructor for Tuple2#

dcTupleN :: Int -> DaCon Name (Type Name) Source #

Data constructor for n-tuples

Primitive Vec operators

xvRep :: Int -> Type Name -> Exp () Name -> Exp () Name Source #

xvProj :: Int -> Int -> Type Name -> Exp () Name -> Exp () Name Source #

xvGather :: Int -> Type Name -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

xvScatter :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

Series operators

xProj :: [Type Name] -> Int -> Exp () Name -> Exp () Name Source #

xRateOfSeries :: TypeF -> TypeF -> TypeF -> ExpF -> ExpF Source #

xNatOfRateNat :: TypeF -> ExpF -> ExpF Source #

xNext :: TypeF -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF Source #

xNextC :: Int -> TypeF -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF Source #

xDown :: Int -> TypeF -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF Source #

xTail :: Int -> TypeF -> TypeF -> TypeF -> ExpF -> ExpF -> ExpF Source #

Control operators

xLoopN :: TypeF -> ExpF -> ExpF -> ExpF Source #

xGuard :: ExpF -> ExpF -> ExpF Source #

xSegment :: ExpF -> ExpF -> ExpF Source #

xSplit :: Int -> TypeF -> ExpF -> ExpF -> ExpF -> ExpF Source #

Store operators

xNew :: Type Name -> Exp () Name -> Exp () Name Source #

xRead :: Type Name -> Exp () Name -> Exp () Name Source #

xWrite :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

xReadVectorC :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

xWriteVector :: Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

xWriteVectorC :: Int -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name -> Exp () Name Source #

xTailVector :: Int -> Type Name -> Type Name -> Exp () Name -> Exp () Name -> Exp () Name Source #