Safe Haskell | None |
---|
Disciple Core Flow is a Domain Specific Language (DSL) for writing first order data flow programs.
- profile :: Profile Name
- data Lifting = Lifting {
- liftingFactor :: Int
- data Config = Config {}
- defaultConfigVector :: Config
- defaultConfigKernel :: Config
- defaultConfigScalar :: Config
- data Method
- = MethodScalar
- | MethodKernel { }
- | MethodVector { }
- lowerModule :: Config -> ModuleF -> Either Error ModuleF
- data Name
- = NameVar String
- | NameVarMod Name String
- | NameCon String
- | NameKiConFlow KiConFlow
- | NameTyConFlow TyConFlow
- | NameDaConFlow DaConFlow
- | NameOpConcrete OpConcrete
- | NameOpControl OpControl
- | NameOpSeries OpSeries
- | NameOpStore OpStore
- | NameOpVector OpVector
- | NamePrimTyCon PrimTyCon
- | NamePrimArith PrimArith
- | NamePrimCast PrimCast
- | NamePrimVec PrimVec
- | NameLitBool Bool
- | NameLitNat Integer
- | NameLitInt Integer
- | NameLitWord Integer Int
- | NameLitFloat Rational Int
- data KiConFlow = KiConFlowRate
- data TyConFlow
- data DaConFlow = DaConFlowTuple Int
- data OpControl
- data OpSeries
- data OpStore
- data OpVector
- data PrimTyCon
- data PrimArith
- = PrimArithNeg
- | PrimArithAdd
- | PrimArithSub
- | PrimArithMul
- | PrimArithDiv
- | PrimArithMod
- | PrimArithRem
- | PrimArithEq
- | PrimArithNeq
- | PrimArithGt
- | PrimArithGe
- | PrimArithLt
- | PrimArithLe
- | PrimArithAnd
- | PrimArithOr
- | PrimArithShl
- | PrimArithShr
- | PrimArithBAnd
- | PrimArithBOr
- | PrimArithBXOr
- data PrimVec
- = PrimVecNeg {
- primVecMulti :: Int
- | PrimVecAdd {
- primVecMulti :: Int
- | PrimVecSub {
- primVecMulti :: Int
- | PrimVecMul {
- primVecMulti :: Int
- | PrimVecDiv {
- primVecMulti :: Int
- | PrimVecRep {
- primVecMulti :: Int
- | PrimVecPack {
- primVecMulti :: Int
- | PrimVecProj {
- primVecMulti :: Int
- primVecIndex :: Int
- | PrimVecGather {
- primVecMulti :: Int
- | PrimVecScatter {
- primVecMulti :: Int
- = PrimVecNeg {
- data PrimCast
- readName :: String -> Maybe Name
- lexModuleString :: String -> Int -> String -> [Token (Tok Name)]
- lexExpString :: String -> Int -> String -> [Token (Tok Name)]
Language profile
Driver
Lifting config controls how many elements should be processed per loop iteration.
Configuration for the lower transform.
defaultConfigVector :: ConfigSource
Config for producing code with vector operations, where the loops handle arbitrary data sizes, of any number of elements.
defaultConfigKernel :: ConfigSource
Config for producing code with vector operations, where the loops just handle a size of data which is an even multiple of the vector width.
defaultConfigScalar :: ConfigSource
Config for producing code with just scalar operations.
What lowering method to use.
MethodScalar | Produce sequential scalar code with nested loops. |
MethodKernel | Produce vector kernel code that only processes an even multiple of the vector width. |
MethodVector | Try to produce sequential vector code, falling back to scalar code if this is not possible. |
lowerModule :: Config -> ModuleF -> Either Error ModuleFSource
Take a module that contains only well formed series processes defined at top-level, and lower them all into procedures.
Names
Names of things used in Disciple Core Flow.
NameVar String | User defined variables. |
NameVarMod Name String | A name generated by modifying some other name `name$mod` |
NameCon String | A user defined constructor. |
NameKiConFlow KiConFlow | Fragment specific kind constructors. |
NameTyConFlow TyConFlow | Fragment specific type constructors. |
NameDaConFlow DaConFlow | Fragment specific data constructors. |
NameOpConcrete OpConcrete | Concrete series operators. |
NameOpControl OpControl | Control operators. |
NameOpSeries OpSeries | Series operators. |
NameOpStore OpStore | Store operators. |
NameOpVector OpVector | Vector operators. |
NamePrimTyCon PrimTyCon | A primitive type constructor. |
NamePrimArith PrimArith | Primitive arithmetic, logic, comparison and bit-wise operators. |
NamePrimCast PrimCast | Primitive casting between numeric types. |
NamePrimVec PrimVec | Primitive vector operators. |
NameLitBool Bool | A boolean literal. |
NameLitNat Integer | A natural literal. |
NameLitInt Integer | An integer literal. |
NameLitWord Integer Int | A word literal, with the given number of bits precision. |
NameLitFloat Rational Int | A float literal, with the given number of bits precision. |
Fragment specific kind constructors.
Fragment specific type constructors.
TyConFlowTuple Int |
|
TyConFlowVector |
|
TyConFlowSeries |
|
TyConFlowSegd |
|
TyConFlowSel Int |
|
TyConFlowRef |
|
TyConFlowWorld |
|
TyConFlowRateNat |
|
TyConFlowDown Int |
|
TyConFlowTail Int |
|
TyConFlowProcess |
|
Primitive data constructors.
DaConFlowTuple Int |
|
Control operators.
Fusable Flow operators that work on Series.
OpSeriesRep | Replicate a single element into a series. |
OpSeriesReps | Segmented replicate. |
OpSeriesIndices | Segmented indices |
OpSeriesFill | Fill an existing vector from a series. |
OpSeriesGather | Gather (read) elements from a vector. |
OpSeriesScatter | Scatter (write) elements into a vector. |
OpSeriesMkSel Int | Make a selector. |
OpSeriesMkSegd | Make a segment descriptor. |
OpSeriesMap Int | Apply a worker to corresponding elements of some series. |
OpSeriesPack | Pack a series according to a flags vector. |
OpSeriesReduce | Reduce a series with an associative operator, updating an existing accumulator. |
OpSeriesFolds | Segmented fold. |
OpSeriesRunProcess Int | Convert vector(s) into series, all with same length with runtime check. |
OpSeriesJoin | Join two series processes. |
Store operators.
OpStoreNew | Allocate a new reference. |
OpStoreRead | Read from a reference. |
OpStoreWrite | Write to a reference. |
OpStoreNewVector | Allocate a new vector (taking a |
OpStoreNewVectorR | Allocate a new vector (taking a |
OpStoreNewVectorN | Allocate a new vector (taking a |
OpStoreReadVector Int | Read a packed Vec of values from a Vector buffer. |
OpStoreWriteVector Int | Write a packed Vec of values to a Vector buffer. |
OpStoreTailVector Int | Window a target vector to the tail of some rate. |
OpStoreTruncVector | Truncate a vector to a smaller length. |
Fusable flow operators that work on Vectors.
OpVectorMap Int | Apply worker function to |
OpVectorFilter | Filter a vector according to a predicate. |
OpVectorReduce | Associative fold. |
OpVectorGenerate | Create a new vector from an index function. |
OpVectorLength | Get a vector's length. |
data PrimTyCon
Primitive type constructors.
PrimTyConVoid |
|
PrimTyConBool |
|
PrimTyConNat |
|
PrimTyConInt |
|
PrimTyConWord Int |
|
PrimTyConFloat Int |
|
PrimTyConVec Int |
|
PrimTyConAddr |
|
PrimTyConPtr |
|
PrimTyConTag |
|
PrimTyConString |
These are primitive until we can define our own unboxed types. |
data PrimArith
Primitive arithmetic, logic, and comparison opretors. We expect the backend/machine to be able to implement these directly.
For the Shift Right operator, the type that it is used at determines whether it is an arithmetic (with sign-extension) or logical (no sign-extension) shift.
PrimArithNeg | Negation |
PrimArithAdd | Addition |
PrimArithSub | Subtraction |
PrimArithMul | Multiplication |
PrimArithDiv | Division |
PrimArithMod | Modulus |
PrimArithRem | Remainder |
PrimArithEq | Equality |
PrimArithNeq | Negated Equality |
PrimArithGt | Greater Than |
PrimArithGe | Greater Than or Equal |
PrimArithLt | Less Than |
PrimArithLe | Less Than or Equal |
PrimArithAnd | Boolean And |
PrimArithOr | Boolean Or |
PrimArithShl | Shift Left |
PrimArithShr | Shift Right |
PrimArithBAnd | Bit-wise And |
PrimArithBOr | Bit-wise Or |
PrimArithBXOr | Bit-wise eXclusive Or |
data PrimVec
Primitive vector operators.
PrimVecNeg | Negate elements of a vector. |
| |
PrimVecAdd | Add elements of a vector. |
| |
PrimVecSub | Subtract elements of a vector. |
| |
PrimVecMul | Multiply elements of a vector. |
| |
PrimVecDiv | Divide elements of a vector. |
| |
PrimVecRep | Replicate a scalar into a vector. |
| |
PrimVecPack | Pack multiple scalars into a vector |
| |
PrimVecProj | Extract a single element from a vector. |
| |
PrimVecGather | Read multiple elements from memory. |
| |
PrimVecScatter | Write multiple elements to memory. |
|
data PrimCast
Primitive cast between two types.
The exact set of available casts is determined by the target platform.
For example, you can only promote a Nat#
to a Word32#
on a 32-bit
system. On a 64-bit system the Nat#
type is 64-bits wide, so casting it
to a Word32#
would be a truncation.
PrimCastConvert | Convert a value to a new representation with the same precision. |
PrimCastPromote | Promote a value to one of similar or larger width, without loss of precision. |
PrimCastTruncate | Truncate a value to a new width, possibly losing precision. |