Safe Haskell | None |
---|
- Names and lexing
- Fragment specific kind constructors
- Fragment specific type constructors
- Fragment specific data constructors
- Fusable Flow operators
- Series operators
- Control operators
- Store operators
- Store operators
- Primitive type constructors
- Primitive arithmetic operators
- Primitive vector operators
- Casting between primitive types
- 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
- readName :: String -> Maybe Name
- data KiConFlow = KiConFlowRate
- readKiConFlow :: String -> Maybe KiConFlow
- data TyConFlow
- readTyConFlow :: String -> Maybe TyConFlow
- kindTyConFlow :: TyConFlow -> Kind Name
- data DaConFlow = DaConFlowTuple Int
- readDaConFlow :: String -> Maybe DaConFlow
- typeDaConFlow :: DaConFlow -> Type Name
- data OpConcrete
- readOpConcrete :: String -> Maybe OpConcrete
- typeOpConcrete :: OpConcrete -> Type Name
- data OpSeries
- readOpSeries :: String -> Maybe OpSeries
- typeOpSeries :: OpSeries -> Type Name
- data OpControl
- readOpControl :: String -> Maybe OpControl
- typeOpControl :: OpControl -> Type Name
- data OpStore
- readOpStore :: String -> Maybe OpStore
- typeOpStore :: OpStore -> Type Name
- data OpVector
- readOpVector :: String -> Maybe OpVector
- typeOpVector :: OpVector -> Type Name
- data PrimTyCon
- kindPrimTyCon :: PrimTyCon -> Kind Name
- data PrimArith
- = PrimArithNeg
- | PrimArithAdd
- | PrimArithSub
- | PrimArithMul
- | PrimArithDiv
- | PrimArithMod
- | PrimArithRem
- | PrimArithEq
- | PrimArithNeq
- | PrimArithGt
- | PrimArithGe
- | PrimArithLt
- | PrimArithLe
- | PrimArithAnd
- | PrimArithOr
- | PrimArithShl
- | PrimArithShr
- | PrimArithBAnd
- | PrimArithBOr
- | PrimArithBXOr
- typePrimArith :: PrimArith -> Type Name
- 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 {
- typePrimVec :: PrimVec -> Type Name
- multiOfPrimVec :: PrimVec -> Maybe Int
- liftPrimArithToVec :: Int -> PrimArith -> Maybe PrimVec
- lowerPrimVecToArith :: PrimVec -> Maybe PrimArith
- data PrimCast
- typePrimCast :: PrimCast -> Type Name
Names and lexing
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 kind constructors.
readKiConFlow :: String -> Maybe KiConFlowSource
Read a kind constructor name.
Fragment specific type constructors
Fragment specific type constructors.
TyConFlowTuple Int |
|
TyConFlowVector |
|
TyConFlowSeries |
|
TyConFlowSegd |
|
TyConFlowSel Int |
|
TyConFlowRef |
|
TyConFlowWorld |
|
TyConFlowRateNat |
|
TyConFlowDown Int |
|
TyConFlowTail Int |
|
TyConFlowProcess |
|
readTyConFlow :: String -> Maybe TyConFlowSource
Read a type constructor name.
kindTyConFlow :: TyConFlow -> Kind NameSource
Yield the kind of a primitive type constructor.
Fragment specific data constructors
Primitive data constructors.
DaConFlowTuple Int |
|
readDaConFlow :: String -> Maybe DaConFlowSource
Read a data constructor name.
typeDaConFlow :: DaConFlow -> Type NameSource
Yield the type of a data constructor.
Fusable Flow operators
data OpConcrete Source
Series related operators. These operators work on series after the code has been fused. They do not appear in the source program.
OpConcreteProj Int Int | Project out a component of a tuple, given the tuple arity and index of the desired component. |
OpConcreteRateOfSeries | Take the rate of a series. |
OpConcreteNatOfRateNat | Take the underlying |
OpConcreteNext Int | Take some elements from a series. |
OpConcreteDown Int | Decimate the rate of a series. |
OpConcreteTail Int | Take the tail rate of a decimated series. |
readOpConcrete :: String -> Maybe OpConcreteSource
Read a series operator name.
typeOpConcrete :: OpConcrete -> Type NameSource
Yield the type of a series operator.
Series 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. |
readOpSeries :: String -> Maybe OpSeriesSource
Read a data flow operator name.
typeOpSeries :: OpSeries -> Type NameSource
Yield the type of a data flow operator,
or error
if there isn't one.
Control operators
Control operators.
readOpControl :: String -> Maybe OpControlSource
Read a control operator name.
typeOpControl :: OpControl -> Type NameSource
Yield the type of a control operator.
Store operators
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. |
readOpStore :: String -> Maybe OpStoreSource
Read a store operator name.
typeOpStore :: OpStore -> Type NameSource
Yield the type of a store operator.
Store operators
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. |
readOpVector :: String -> Maybe OpVectorSource
Read a data flow operator name.
typeOpVector :: OpVector -> Type NameSource
Yield the type of a data flow operator,
or error
if there isn't one.
Primitive type constructors
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. |
kindPrimTyCon :: PrimTyCon -> Kind NameSource
Yield the kind of a type constructor.
Primitive arithmetic operators
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 |
typePrimArith :: PrimArith -> Type NameSource
Take the type of a primitive arithmetic operator.
Primitive vector operators
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. |
|
typePrimVec :: PrimVec -> Type NameSource
Take the type of a primitive vector operator.
multiOfPrimVec :: PrimVec -> Maybe Int
Yield the multiplicity of a vector operator.
liftPrimArithToVec :: Int -> PrimArith -> Maybe PrimVec
Yield the PrimVector
that corresponds to a PrimArith
of the
given multiplicity, if any.
lowerPrimVecToArith :: PrimVec -> Maybe PrimArith
Yield the PrimArith
that corresponds to a PrimVector
, if any.
Casting between primitive types
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. |
typePrimCast :: PrimCast -> Type NameSource
Take the type of a primitive cast.