Feldspar.Core.Expr
Contents
Description
- data Data a = Typeable a => Data (Ref (Expr a))
- ref :: Typeable a => Expr a -> Data a
- refId :: Data a -> Unique
- deref :: Data a -> Expr a
- typeOfData :: forall a. Typeable a => Data a -> Tuple StorableType
- data Expr a where
- Input :: Expr a
- Value :: Storable a => a -> Expr a
- Tuple2 :: Data a -> Data b -> Expr (a, b)
- Tuple3 :: Data a -> Data b -> Data c -> Expr (a, b, c)
- Tuple4 :: Data a -> Data b -> Data c -> Data d -> Expr (a, b, c, d)
- GetTuple :: GetTuple n a => T n -> Data a -> Expr (Part n a)
- Function :: String -> (a -> b) -> Data a -> Expr b
- NoInline :: (Typeable a, Typeable b) => String -> Ref (Data a -> Data b) -> Data a -> Expr b
- IfThenElse :: (Typeable a, Typeable b) => Data Bool -> (Data a -> Data b) -> (Data a -> Data b) -> Data a -> Expr b
- While :: Typeable a => (Data a -> Data Bool) -> (Data a -> Data a) -> Data a -> Expr a
- Parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Expr (n :> a)
- class Typeable (Internal a) => Computable a where
- type Internal a
- internalize :: a -> Data (Internal a)
- externalize :: Data (Internal a) -> a
- wrap :: (Computable a, Computable b) => (a -> b) -> Data (Internal a) -> Data (Internal b)
- unwrap :: (Computable a, Computable b) => (Data (Internal a) -> Data (Internal b)) -> a -> b
- evalE :: Expr a -> a
- evalD :: Data a -> a
- eval :: Computable a => a -> Internal a
- value_ :: Storable a => a -> Data a
- value :: Primitive a => a -> Data a
- unit :: Data ()
- true :: Data Bool
- false :: Data Bool
- array :: (NaturalT n, Storable a) => ListBased (n :> a) -> Data (n :> a)
- size :: (NaturalT n, Storable a) => Data (n :> a) -> [Int]
- function :: (Storable a, Storable b) => String -> (a -> b) -> Data a -> Data b
- function2 :: (Storable a, Storable b, Storable c) => String -> (a -> b -> c) -> Data a -> Data b -> Data c
- function3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data d
- function4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data e
- functionFold :: (Storable a, Storable b) => String -> (a -> b) -> Data a -> Data b
- functionFold2 :: (Storable a, Storable b, Storable c) => String -> (a -> b -> c) -> Data a -> Data b -> Data c
- functionFold3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data d
- functionFold4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data e
- getIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data a
- setIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data a -> Data (n :> a)
- class RandomAccess a where
- noInline :: (Computable a, Computable b) => String -> (a -> b) -> a -> b
- ifThenElse :: (Computable a, Computable b) => Data Bool -> (a -> b) -> (a -> b) -> a -> b
- while :: Computable a => (a -> Data Bool) -> (a -> a) -> a -> a
- parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Data (n :> a)
- data Info = Info {}
- type GraphBuilder a = WriterT [Node] (State Info) a
- startInfo :: Info
- runGraph :: GraphBuilder a -> Info -> (a, ([Node], Info))
- newIndex :: GraphBuilder NodeId
- remember :: Data a -> NodeId -> GraphBuilder ()
- checkNode :: Data a -> GraphBuilder (Maybe NodeId)
- tupleBind :: Typeable a => NodeId -> T a -> Tuple Variable
- node :: forall a. Typeable a => Data a -> Function -> Tuple Source -> Tuple StorableType -> GraphBuilder ()
- sourceNode :: Data a -> Function -> GraphBuilder ()
- source :: forall a. [Int] -> Data a -> GraphBuilder Source
- traceTuple :: Data a -> GraphBuilder (Tuple Source)
- buildGraph :: forall a. Data a -> GraphBuilder ()
- buildSubFun :: forall a b. (Typeable a, Typeable b) => (Data a -> Data b) -> GraphBuilder Interface
- toGraphD :: (Typeable a, Typeable b) => (Data a -> Data b) -> Graph
- class Program a where
- showCore :: forall a. Program a => a -> String
- printCore :: Program a => a -> IO ()
Expressions
A wrapper around Expr to allow observable sharing (see
Feldspar.Core.Ref).
Instances
| Eq (Data a) | |
| Fractional (Data Float) | |
| (Num n, Primitive n) => Num (Data n) | |
| Ord (Data a) | |
| Primitive a => Show (Data a) | |
| (NaturalT n, Storable a) => RandomAccess (Data (:> n a)) | |
| Storable a => Computable (Data a) | |
| (NaturalT n1, NaturalT n2, Storable a, AccessPattern t1, AccessPattern t2) => Computable (:>> (t1 n1) (:>> (t2 n2) (Data a))) | |
| (NaturalT n, Storable a, AccessPattern t) => Computable (:>> (t n) (Data a)) |
typeOfData :: forall a. Typeable a => Data a -> Tuple StorableTypeSource
Typed core language expressions. A value of type Expr a can be thought of
as a representation of a program that computes a value of type a.
Constructors
| Input :: Expr a | |
| Value :: Storable a => a -> Expr a | |
| Tuple2 :: Data a -> Data b -> Expr (a, b) | |
| Tuple3 :: Data a -> Data b -> Data c -> Expr (a, b, c) | |
| Tuple4 :: Data a -> Data b -> Data c -> Data d -> Expr (a, b, c, d) | |
| GetTuple :: GetTuple n a => T n -> Data a -> Expr (Part n a) | |
| Function :: String -> (a -> b) -> Data a -> Expr b | |
| NoInline :: (Typeable a, Typeable b) => String -> Ref (Data a -> Data b) -> Data a -> Expr b | |
| IfThenElse :: (Typeable a, Typeable b) => Data Bool -> (Data a -> Data b) -> (Data a -> Data b) -> Data a -> Expr b | |
| While :: Typeable a => (Data a -> Data Bool) -> (Data a -> Data a) -> Data a -> Expr a | |
| Parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Expr (n :> a) |
class Typeable (Internal a) => Computable a whereSource
Computable types. A computable value completely represents a core program,
in such a way that internalize . externalize preserves semantics, but not
necessarily syntax.
The terminology used in this class comes from thinking of the Data type as
the "internal core language" and the core API as the "external core
language".
Associated Types
The internal representation of the type a (without the Data
constructor).
Methods
internalize :: a -> Data (Internal a)Source
Convert to internal representation
externalize :: Data (Internal a) -> aSource
Convert to external representation
Instances
| Storable a => Computable (Data a) | |
| (Computable a, Computable b) => Computable (a, b) | |
| (NaturalT n1, NaturalT n2, Storable a, AccessPattern t1, AccessPattern t2) => Computable (:>> (t1 n1) (:>> (t2 n2) (Data a))) | |
| (NaturalT n, Storable a, AccessPattern t) => Computable (:>> (t n) (Data a)) | |
| (Computable a, Computable b, Computable c) => Computable (a, b, c) | |
| (Computable a, Computable b, Computable c, Computable d) => Computable (a, b, c, d) |
wrap :: (Computable a, Computable b) => (a -> b) -> Data (Internal a) -> Data (Internal b)Source
unwrap :: (Computable a, Computable b) => (Data (Internal a) -> Data (Internal b)) -> a -> bSource
eval :: Computable a => a -> Internal aSource
Evaluation of any Computable type
value :: Primitive a => a -> Data aSource
A primitive value (a program that computes a constant value)
array :: (NaturalT n, Storable a) => ListBased (n :> a) -> Data (n :> a)Source
For example,
array [[1,2,3],[4,5]] :: Data (D2 :> D4 :> Int)
is a 2x4-element array of Ints, with the first row initialized to [1,2,3]
and the second row to [4,5].
size :: (NaturalT n, Storable a) => Data (n :> a) -> [Int]Source
Returns the size of each level of a multi-dimensional array, starting with the outermost level.
function :: (Storable a, Storable b) => String -> (a -> b) -> Data a -> Data bSource
A one-argument primitive function. The first argument is the name of the function, and the second argument gives its evaluation semantics.
function2 :: (Storable a, Storable b, Storable c) => String -> (a -> b -> c) -> Data a -> Data b -> Data cSource
A two-argument function
function3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data dSource
A three-argument function
function4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data eSource
A four-argument function
functionFold :: (Storable a, Storable b) => String -> (a -> b) -> Data a -> Data bSource
A one-argument function with constant folding
functionFold2 :: (Storable a, Storable b, Storable c) => String -> (a -> b -> c) -> Data a -> Data b -> Data cSource
A two-argument function with constant folding
functionFold3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data dSource
A three-argument function with constant folding
functionFold4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data eSource
A four-argument function with constant folding
getIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data aSource
Look up an index in an array
setIx :: forall n a. (NaturalT n, Storable a) => Data (n :> a) -> Data Int -> Data a -> Data (n :> a)Source
setIx arr i a:
Replaces the value at index i in the array arr with the value a.
class RandomAccess a whereSource
Instances
| (NaturalT n, Storable a) => RandomAccess (Data (:> n a)) | |
| RandomAccess (:>> (Par n) a) |
noInline :: (Computable a, Computable b) => String -> (a -> b) -> a -> bSource
Constructs a non-primitive, non-inlined function.
The normal way to make a non-primitive function is to use an ordinary Haskell function, for example:
myFunc x = x * 4 + 5
However, such functions are inevitably inlined into the program expression
when applied. noInline can be thought of as a way to protect a function
against inlining (but later transformations may choose to inline anyway).
Ideally, it should be posssible to reuse such a function several times, but
at the moment this does not work. Every application of a noInline function
results in a new copy of the function in the core program.
ifThenElse :: (Computable a, Computable b) => Data Bool -> (a -> b) -> (a -> b) -> a -> bSource
ifThenElse cond thenFunc elseFunc:
Selects between the two functions thenFunc and elseFunc depending on
whether the condition cond is true or false.
while :: Computable a => (a -> Data Bool) -> (a -> a) -> a -> aSource
while cont body:
A while-loop. The condition cont determines whether the loop should
continue one more iteration. body computes the next state. The result is a
function from initial state to final state.
parallel :: (NaturalT n, Storable a) => Data Int -> (Data Int -> Data a) -> Data (n :> a)Source
parallel sz ixf:
Parallel tiling. Computes the elements of a vector. sz is the dynamic size,
i.e. how many of the allocated elements that should be computed. The function
ixf maps each index to its value.
Since there are no dependencies between the elements, the compiler is free to compute the elements in parallel (or any other order).
Graph conversion
node :: forall a. Typeable a => Data a -> Function -> Tuple Source -> Tuple StorableType -> GraphBuilder ()Source
Declare a node
sourceNode :: Data a -> Function -> GraphBuilder ()Source
Declare a source node (one with no inputs)
traceTuple :: Data a -> GraphBuilder (Tuple Source)Source
buildGraph :: forall a. Data a -> GraphBuilder ()Source
buildSubFun :: forall a b. (Typeable a, Typeable b) => (Data a -> Data b) -> GraphBuilder InterfaceSource
Types that represents core language programs
Methods
Converts a program to a Graph
Instances
| Computable a => Program a | |
| (Computable a, Computable b, Computable c, Computable d, Computable e) => Program (a -> b -> c -> d -> e) | |
| (Computable a, Computable b, Computable c, Computable d) => Program (a -> b -> c -> d) | |
| (Computable a, Computable b, Computable c) => Program (a -> b -> c) | |
| (Computable a, Computable b) => Program (a -> b) |