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

Safe HaskellNone
LanguageHaskell98

DDC.Core.Flow

Contents

Description

Disciple Core Flow is a Domain Specific Language (DSL) for writing first order data flow programs.

Synopsis

Language profile

profile :: Profile Name Source

Language profile for Disciple Core Flow.

Driver

data Lifting Source

Lifting config controls how many elements should be processed per loop iteration.

Constructors

Lifting 

Fields

liftingFactor :: Int
 

data Config Source

Configuration for the lower transform.

Constructors

Config 

Fields

configMethod :: Method
 

defaultConfigVector :: Config Source

Config for producing code with vector operations, where the loops handle arbitrary data sizes, of any number of elements.

defaultConfigKernel :: Config Source

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 :: Config Source

Config for producing code with just scalar operations.

data Method Source

What lowering method to use.

Constructors

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 ModuleF Source

Take a module that contains some well formed series processes defined at top-level, and lower them into procedures.

Names

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.

data KiConFlow Source

Fragment specific kind constructors.

data TyConFlow Source

Fragment specific type constructors.

Constructors

TyConFlowTuple Int

TupleN# constructor. Tuples.

TyConFlowVector

Vector# constructor. Vector is a pair of mutable length and mutable data

TyConFlowBuffer

Buffer# constructor. Mutable Buffer with no associated length

TyConFlowRateVec

RateVec# constructor. Vector is a pair of mutable length and mutable data

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.

TyConFlowRateCross

Multiply two Rates together

TyConFlowRateAppend

Add two Rates together

TyConFlowDown Int

DownN# constructor. Rate decimation.

TyConFlowTail Int

TailN# constructor. Rate tail after decimation.

TyConFlowProcess

Process constructor.

TyConFlowResize

Resize p j k is a witness that Process p j can be resized to Process p k

data DaConFlow Source

Primitive data constructors.

Constructors

DaConFlowTuple Int

TN data constructor.

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.

OpSeriesGenerate

Generate a new series with size based on klok/rate

OpSeriesReduce

Reduce a series with an associative operator, updating an existing accumulator.

OpSeriesFolds

Segmented fold.

OpSeriesRunProcess

Execute a process

OpSeriesRunProcessUnit

Introduce a Proc type, but argument returns unit instead of process Has exact same type as RunProcess except for that, so that they can easily be swapped during lowering

OpSeriesRateVecsOfVectors Int

Convert vector(s) into manifests, all with same length with runtime check.

OpSeriesSeriesOfRateVec

Convert manifest into series

OpSeriesAppend

Append two series

OpSeriesCross

Cross a series and a vector

OpSeriesResizeProc

Resize a process

OpSeriesResizeId

Resize a process

OpSeriesResizeAppL

Inject a series into the left side of an append

OpSeriesResizeAppR

Inject a series into the right side of an append

OpSeriesResizeApp

Map over the contents of an append

OpSeriesResizeSel1

Move from filtered to filtee

OpSeriesResizeSegd

Move from segment data to segment lens

OpSeriesResizeCross

Move from (cross a b) to a

OpSeriesJoin

Join two series processes.

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.

OpStoreBufOfVector

Get a vector's data buffer

OpStoreBufOfRateVec

Get a vector's data buffer

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.

OpVectorGather

Gather (read) elements from a vector:

gather v ix = map (v!) ix

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 necessearily enough precision to count every byte of memory.

PrimTyConInt

Int# signed integers. Enough precision to count every object in the heap, but NOT necessearily 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.

PrimTyConSize

Size# unsigned sizes. Enough precision to count every addressable bytes of memory.

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# like Addr#, but with a region and element type annotation. In particular, a value of a type like (Ptr) must be at least 4-byte aligned and point to memory owned by the current process.

PrimTyConTextLit

TextLit# type of a text literal, which is represented as a pointer to the literal data in static memory.

PrimTyConTag

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

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

data PrimVec :: *

Primitive fixed-length SIMD 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
 

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.

Name Parsing

readName :: String -> Maybe Name Source

Read the name of a variable, constructor or literal.

Program Lexing

lexModuleString :: String -> Int -> String -> [Token (Tok Name)] Source

Lex a string to tokens, using primitive names.

The first argument gives the starting source line number.

lexExpString :: String -> Int -> String -> [Token (Tok Name)] Source

Lex a string to tokens, using primitive names.

The first argument gives the starting source line number.