Paraiso-0.3.1.5: a code generator for partial differential equations solvers.

Safe HaskellNone
LanguageHaskell2010

Language.Paraiso.OM.Builder.Internal

Description

A monadic library to build dataflow graphs for OM. Builder is only for Graph vector gauge () . Graphs with other annotation types can be created by fmap. This module exports everything, for writing other Builder modules.

Synopsis

Documentation

type Builder vector gauge anot val = State (BuilderState vector gauge anot) val Source

The Builder monad is used to build Kernels.

data BuilderState vector gauge anot Source

Constructors

BuilderState 

Fields

setup :: Setup vector gauge anot
 
context :: BuilderContext anot
 
target :: Graph vector gauge anot
 

Instances

(Show anot, Show (vector gauge)) => Show (BuilderState vector gauge anot) Source 
Eq (Builder v g a ret) Source 
(TRealm r, Typeable * c, C c, Fractional c) => Fractional (Builder v g a (Value r c)) Source

you can convert GHC floating point immediates to Builder.

(TRealm r, Typeable * c, C c) => Num (Builder v g a (Value r c)) Source

you can convert GHC numeric immediates to Builder.

Show (Builder v g a ret) Source 
(TRealm r, Typeable * c) => C (Builder v g a (Value r c)) Source

choose the larger or the smaller of the two.

(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source 
(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source

Builder is Algebraic C. You can use sqrt and so on.

(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source

Builder is Field C. You can use /, recip.

(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source 
(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source

Builder is Ring C. You can use div and mod.

(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source

Builder is Ring C. You can use one, *.

(TRealm r, Typeable * c) => C (Builder v g a (Value r c)) Source 
(TRealm r, Typeable * c, C c) => C (Builder v g a (Value r c)) Source

Builder is Additive C. You can use zero, +, -, negate.

TRealm r => Boolean (Builder v g a (Value r Bool)) Source

Builder is Boolean. You can use true, false, not, &&, ||.

type B ret = forall v g a. Builder v g a ret Source

type BuilderOf r c = forall v g a. Builder v g a (Value r c) Source

buildKernel Source

Arguments

:: Setup v g a

The Orthotope machine setup.

-> Name

The name of the kernel.

-> Builder v g a ()

The builder monad.

-> Kernel v g a

The created kernel.

Create a Kernel from a Builder monad.

initState :: Setup v g a -> BuilderState v g a Source

Create an initial state for Builder monad from a OM Setup.

modifyG Source

Arguments

:: (Graph v g a -> Graph v g a)

The graph modifying function.

-> Builder v g a ()

The state gets silently modified.

Modify the dataflow graph stored in the Builder.

getG :: Builder v g a (Graph v g a) Source

Get the graph stored in the Builder.

freeNode :: B Node Source

get the number of the next unoccupied Node in the graph.

addNode Source

Arguments

:: [Node]

The list of dependent nodes. The order is recorded.

-> Node v g a

The new node to be added.

-> Builder v g a Node 

add a node to the graph.

addNodeE Source

Arguments

:: [Node]

The list of dependent nodes. The order is recorded.

-> (a -> Node v g a)

The new node to be added, with Annotation missing.

-> Builder v g a Node 

add a node to the graph with an empty Annotation.

valueToNode :: (TRealm r, Typeable c) => Value r c -> B Node Source

convert a Value to a

lookUpStatic :: Named DynValue -> B StaticIdx Source

look up the Named DynValue with the correct name and type is included in the staticValues of the BuilderState

bind :: (Monad m, Functor m) => m a -> m (m a) Source

run the given builder monad, get the result graph node, and wrap it in a return monad for later use. it is like binding a value to a monad-level identifier.

load Source

Arguments

:: (TRealm r, Typeable c) 
=> Named (StaticValue r c)

the named static value to be loaded from.

-> B (Value r c)

The loaded Value as a result.

Load from a static value.

store Source

Arguments

:: (TRealm r, Typeable c) 
=> Named (StaticValue r c)

the named static value to be stored on.

-> Builder v g a (Value r c)

The Value to be stored.

-> Builder v g a ()

The result.

Store to a static value.

reduce Source

Arguments

:: Typeable c 
=> Operator

The reduction Operator.

-> Builder v g a (Value TArray c)

The TArray Value to be reduced.

-> Builder v g a (Value TScalar c)

The TScalar Value that holds the reduction result.

Reduce over a TArray Value using the specified reduction Operator to make a TScalar Value

broadcast Source

Arguments

:: Typeable c 
=> Builder v g a (Value TScalar c)

The TScalar Value to be broadcasted.

-> Builder v g a (Value TArray c)

The TArray Value, all of them containing the global value.

Broadcast a TScalar Value to make it a TArray Value

loadIndex Source

Arguments

:: Typeable g 
=> Axis v

The axis for which index is required

-> Builder v g a (Value TArray g)

The TArray Value that contains the address as a result.

Load the Axis component of the mesh address, to a TArray Value.

loadSize Source

Arguments

:: Typeable g 
=> Axis v

The axis for which the size is required

-> Builder v g a (Value TScalar g)

The TScalar Value that contains the size of the mesh in that direction.

Load the Axis component of the mesh size, to a TScalar Value..

shift Source

Arguments

:: Typeable c 
=> v g

The amount of shift

-> Builder v g a (Value TArray c)

The TArray Value to be shifted

-> Builder v g a (Value TArray c)

The shifted TArray Value as a result.

Shift a TArray Value with a constant vector.

imm Source

Arguments

:: (TRealm r, Typeable c) 
=> c

A Haskell value of type c to be stored.

-> B (Value r c)

TArray Value with the c stored.

Create an immediate Value from a Haskell concrete value. TRealm is type-inferred.

mkOp1 Source

Arguments

:: (TRealm r, Typeable c) 
=> Operator

The operator symbol

-> Builder v g a (Value r c)

Input

-> Builder v g a (Value r c)

Output

Make a unary operator

mkOp2 Source

Arguments

:: (TRealm r, Typeable c) 
=> Operator

The operator symbol

-> Builder v g a (Value r c)

Input 1

-> Builder v g a (Value r c)

Input 2

-> Builder v g a (Value r c)

Output

Make a binary operator

cast :: (TRealm r, Typeable c1, Typeable c2) => Builder v g a (Value r c1) -> Builder v g a (Value r c2) Source

Perform the cast that keeps the realm while change the content type from c1 to c2.

castTo :: (TRealm r, Typeable c1, Typeable c2) => c2 -> Builder v g a (Value r c1) -> Builder v g a (Value r c2) Source

take a phantom object c2, and perform the cast that keeps the realm while change the content type from c1 to c2.

annotate :: (TRealm r, Typeable c) => (a -> a) -> Builder v g a (Value r c) -> Builder v g a (Value r c) Source

Execute the builder, and annotate the very result with the givin function.

(<?>) :: (TRealm r, Typeable c) => (a -> a) -> Builder v g a (Value r c) -> Builder v g a (Value r c) infixr 0 Source

(?) = annotate

withAnnotation :: (a -> a) -> Builder v g a ret -> Builder v g a ret Source

Execute the builder under modifed annotation.