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

Safe HaskellNone

DDC.Core.Flow.Prim

Contents

Synopsis

Names and lexing

data Name Source

Names of things used in Disciple Core Flow.

Constructors

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.

readName :: String -> Maybe NameSource

Read the name of a variable, constructor or literal.

Fragment specific kind constructors

data KiConFlow Source

Fragment specific kind constructors.

Constructors

KiConFlowRate 

readKiConFlow :: String -> Maybe KiConFlowSource

Read a kind constructor name.

Fragment specific type constructors

data TyConFlow Source

Fragment specific type constructors.

Constructors

TyConFlowTuple Int

TupleN# constructor. Tuples.

TyConFlowVector

Vector# constructor. Vectors.

TyConFlowSeries

Series# constructor. Series types.

TyConFlowSegd

Segd# constructor. Segment Descriptors.

TyConFlowSel Int

SelN# constructor. Selectors.

TyConFlowRef

Ref# constructor. References.

TyConFlowWorld

World# constructor. State token used when converting to GHC core.

TyConFlowRateNat

RateNat# constructor. Naturals witnessing a type-level Rate.

TyConFlowDown Int

DownN# constructor. Rate decimation.

TyConFlowTail Int

TailN# constructor. Rate tail after decimation.

TyConFlowProcess

Process constructor.

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

data DaConFlow Source

Primitive data constructors.

Constructors

DaConFlowTuple Int

TN data constructor.

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.

Constructors

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 Nat of a RateNat.

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

data OpSeries Source

Fusable Flow operators that work on Series.

Constructors

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

readOpControl :: String -> Maybe OpControlSource

Read a control operator name.

typeOpControl :: OpControl -> Type NameSource

Yield the type of a control operator.

Store operators

data OpStore Source

Store operators.

Constructors

OpStoreNew

Allocate a new reference.

OpStoreRead

Read from a reference.

OpStoreWrite

Write to a reference.

OpStoreNewVector

Allocate a new vector (taking a Nat for the length)

OpStoreNewVectorR

Allocate a new vector (taking a Rate for the length)

OpStoreNewVectorN

Allocate a new vector (taking a RateNat for the length)

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

data OpVector Source

Fusable flow operators that work on Vectors.

Constructors

OpVectorMap Int

Apply worker function to n vectors zipped.

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.

Constructors

PrimTyConVoid

Void# the Void type has no values.

PrimTyConBool

Bool# unboxed booleans.

PrimTyConNat

Nat# natural numbers. Enough precision to count every object in the heap, but NOT enough precision to count every byte of memory.

PrimTyConInt

Int# signed integers. Enough precision to count every object in the heap, but NOT enough precision to count every byte of memory. If N is the total number of objects that can exist in the heap, then the range of Int# is at least (-N .. +N) inclusive.

PrimTyConWord Int

WordN# machine words of the given width.

PrimTyConFloat Int

FloatN# floating point numbers of the given width.

PrimTyConVec Int

VecN# a packed vector of N values. This is intended to have kind (Data -> Data), so we use concrete vector types like Vec4.

PrimTyConAddr

Addr# a relative or absolute machine address. Enough precision to count every byte of memory. Unlike pointers below, an absolute Addr# need not refer to memory owned by the current process.

PrimTyConPtr

Ptr# should point to a well-formed object owned by the current process.

PrimTyConTag

Tag# data constructor tags. Enough precision to count every possible alternative of an enumerated type.

PrimTyConString

String# of UTF8 characters.

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.

Constructors

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.

Constructors

PrimVecNeg

Negate elements of a vector.

Fields

primVecMulti :: Int
 
PrimVecAdd

Add elements of a vector.

Fields

primVecMulti :: Int
 
PrimVecSub

Subtract elements of a vector.

Fields

primVecMulti :: Int
 
PrimVecMul

Multiply elements of a vector.

Fields

primVecMulti :: Int
 
PrimVecDiv

Divide elements of a vector.

Fields

primVecMulti :: Int
 
PrimVecRep

Replicate a scalar into a vector.

Fields

primVecMulti :: Int
 
PrimVecPack

Pack multiple scalars into a vector

Fields

primVecMulti :: Int
 
PrimVecProj

Extract a single element from a vector.

PrimVecGather

Read multiple elements from memory.

Fields

primVecMulti :: Int
 
PrimVecScatter

Write multiple elements to memory.

Fields

primVecMulti :: Int
 

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.

Constructors

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.