feldspar-language-0.3: A functional embedded language for DSP and parallelismSource codeContentsIndex
Feldspar.Core
Description
The user interface of the core language
Synopsis
data Ord a => Range a = Range {
lowerBound :: Maybe a
upperBound :: Maybe a
}
data a :> b = a :> b
class Set a where
universal :: a
type Length = Int
type Unsigned32 = Word32
type Signed32 = Int32
type Unsigned16 = Word16
type Signed16 = Int16
type Unsigned8 = Word8
type Signed8 = Int8
class Typeable a => Storable a
data Data a
dataSize :: Data a -> Size a
class Typeable (Internal a) => Computable a where
type Internal a
eval :: Computable a => a -> Internal a
value :: Storable a => a -> Data a
array :: Storable a => Size a -> a -> Data a
arrayLen :: Storable a => Data Length -> [a] -> Data [a]
unit :: Data ()
true :: Data Bool
false :: Data Bool
size :: forall a. Storable a => Data [a] -> [Range Length]
cap :: (Storable a, Size a ~ Range b, Ord b) => Range b -> Data a -> Data a
function :: (Storable a, Storable b) => String -> (Size a -> Size b) -> (a -> b) -> Data a -> Data b
function2 :: (Storable a, Storable b, Storable c) => String -> (Size a -> Size b -> Size c) -> (a -> b -> c) -> Data a -> Data b -> Data c
function3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (Size a -> Size b -> Size c -> Size d) -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data d
function4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (Size a -> Size b -> Size c -> Size d -> Size e) -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data e
getIx :: Storable a => Data [a] -> Data Int -> Data a
setIx :: Storable a => Data [a] -> Data Int -> Data a -> Data [a]
class RandomAccess a where
type Element a
(!) :: a -> Data Int -> Element a
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 state => (state -> Data Bool) -> (state -> state) -> state -> state
parallel :: Storable a => Data Length -> (Data Int -> Data a) -> Data [a]
class Program a
showCore :: forall a. Program a => a -> String
showCoreWithSize :: forall a. Program a => a -> String
printCore :: Program a => a -> IO ()
printCoreWithSize :: Program a => a -> IO ()
module Feldspar.Core.Functions
trace :: Storable a => Int -> Data a -> Data a
Documentation
data Ord a => Range a Source
Constructors
Range
lowerBound :: Maybe a
upperBound :: Maybe a
show/hide Instances
Ord a => Eq (Range a)
(Ord a, Num a) => Num (Range a)
(Ord a, Show a) => Show (Range a)
(Arbitrary a, Ord a, Num a) => Arbitrary (Range a)
(Ord a, Num a) => Monoid (Range a)
Ord a => Set (Range a)
data a :> b Source
Heterogeneous list
Constructors
a :> b
show/hide Instances
(Eq a, Eq b) => Eq (:> a b)
(Ord a, Ord b) => Ord (:> a b)
(Show a, Show b) => Show (:> a b)
(Monoid a, Monoid b) => Monoid (:> a b)
(Set a, Set b) => Set (:> a b)
class Set a whereSource
Methods
universal :: aSource
show/hide Instances
Set ()
Ord a => Set (Range a)
(Set a, Set b) => Set (a, b)
(Set a, Set b) => Set (:> a b)
(Set a, Set b, Set c) => Set (a, b, c)
(Set a, Set b, Set c, Set d) => Set (a, b, c, d)
type Length = IntSource
type Unsigned32 = Word32Source
type Signed32 = Int32Source
type Unsigned16 = Word16Source
type Signed16 = Int16Source
type Unsigned8 = Word8Source
type Signed8 = Int8Source
class Typeable a => Storable a Source
Storable types (zero- or higher-level arrays of primitive data).
show/hide Instances
data Data a Source
A wrapper around Expr to allow observable sharing (see Feldspar.Core.Ref) and for memoizing size information.
show/hide Instances
dataSize :: Data a -> Size aSource
class Typeable (Internal a) => Computable a Source

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 Feldspar.Core API as the "external" core language.

Associated Types
type Internal a Source
Data (Internal a) is the internal representation of the type a.
Methods
show/hide Instances
eval :: Computable a => a -> Internal aSource
The semantics of any Computable type
value :: Storable a => a -> Data aSource
A program that computes a constant value
array :: Storable a => Size a -> a -> Data aSource

Like value but with an extra Size argument that can be used to increase the size beyond the given data.

Example 1:

 array (10 :> 20 :> universal) [] :: Data [[Int]]

gives an uninitialized 10x20 array of Int elements.

Example 2:

 array (10 :> 20 :> universal) [[1,2,3]] :: Data [[Int]]

gives a 10x20 array whose first row is initialized to [1,2,3].

arrayLen :: Storable a => Data Length -> [a] -> Data [a]Source
unit :: Data ()Source
true :: Data BoolSource
false :: Data BoolSource
size :: forall a. Storable a => Data [a] -> [Range Length]Source
Returns the size of each level of a multi-dimensional array, starting with the outermost level.
cap :: (Storable a, Size a ~ Range b, Ord b) => Range b -> Data a -> Data aSource
function :: (Storable a, Storable b) => String -> (Size a -> Size b) -> (a -> b) -> Data a -> Data bSource

Constructs a one-argument primitive function.

function fun szf f:

  • fun is the name of the function.
  • szf computes the output size from the input size.
  • f gives the evaluation semantics.
function2 :: (Storable a, Storable b, Storable c) => String -> (Size a -> Size b -> Size c) -> (a -> b -> c) -> Data a -> Data b -> Data cSource
A two-argument primitive function
function3 :: (Storable a, Storable b, Storable c, Storable d) => String -> (Size a -> Size b -> Size c -> Size d) -> (a -> b -> c -> d) -> Data a -> Data b -> Data c -> Data dSource
A three-argument primitive function
function4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) => String -> (Size a -> Size b -> Size c -> Size d -> Size e) -> (a -> b -> c -> d -> e) -> Data a -> Data b -> Data c -> Data d -> Data eSource
A four-argument primitive function
getIx :: Storable a => Data [a] -> Data Int -> Data aSource
Look up an index in an array (see also !)
setIx :: Storable a => Data [a] -> Data Int -> Data a -> Data [a]Source

setIx arr i a:

Replaces the value at index i in the array arr with the value a.

class RandomAccess a whereSource
Associated Types
type Element a Source
The type of elements in a random access structure
Methods
(!) :: a -> Data Int -> Element aSource
Index lookup in a random access structure
show/hide Instances
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 state => (state -> Data Bool) -> (state -> state) -> state -> stateSource

While-loop

while cont body :: state -> state:

  • state is the type of the state.
  • cont determines whether or not to continue based on the current state.
  • body computes the next state from the current state.
  • The result is a function from initial state to final state.
parallel :: Storable a => Data Length -> (Data Int -> Data a) -> Data [a]Source

Parallel array

parallel l ixf:

  • l is the length of the resulting array (outermost level).
  • ifx is a function that maps each index in the range [0 .. l-1] to its element.

Since there are no dependencies between the elements, the compiler is free to compute the elements in any order, or even in parallel.

class Program a Source
Types that represent core language programs
show/hide 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)
(Computable a, Computable b) => Program (a, b)
(Computable a, Computable b, Computable c) => Program (a, b, c)
(Computable a, Computable b, Computable c, Computable d) => Program (a, b, c, d)
showCore :: forall a. Program a => a -> StringSource
Shows the core code generated by the program.
showCoreWithSize :: forall a. Program a => a -> StringSource
Shows the core code with size information as comments.
printCore :: Program a => a -> IO ()Source
printCore = putStrLn . showCore
printCoreWithSize :: Program a => a -> IO ()Source
printCoreWithSize = putStrLn . showCoreWithSize
module Feldspar.Core.Functions
trace :: Storable a => Int -> Data a -> Data aSource
Produced by Haddock version 2.6.1