raw-feldspar-0.1: Resource-Aware Feldspar

Safe HaskellNone
LanguageHaskell2010

Feldspar.Frontend

Contents

Synopsis

Pure expressions

General constructs

share Source #

Arguments

:: (Syntax a, Syntax b) 
=> a

Value to share

-> (a -> b)

Body in which to share the value

-> b 

Force evaluation of a value and share the result. Note that due to common sub-expression elimination, this function is rarely needed in practice.

shareTag Source #

Arguments

:: (Syntax a, Syntax b) 
=> String

A tag (that may be empty). May be used by a back end to generate a sensible variable name.

-> a

Value to share

-> (a -> b)

Body in which to share the value

-> b 

Explicit tagged sharing

forLoop :: Syntax st => Data Length -> st -> (Data Index -> st -> st) -> st Source #

For loop

cond Source #

Arguments

:: Syntax a 
=> Data Bool

Condition

-> a

True branch

-> a

False branch

-> a 

Conditional expression

(?) infixl 1 Source #

Arguments

:: Syntax a 
=> Data Bool

Condition

-> a

True branch

-> a

False branch

-> a 

Condition operator; use as follows:

cond1 ? a $
cond2 ? b $
cond3 ? c $
        default

switch Source #

Arguments

:: (Syntax a, Syntax b, PrimType (Internal a)) 
=> b

Default result

-> [(a, b)]

Cases (match, result)

-> a

Scrutinee

-> b

Result

Multi-way conditional expression

The first association (a,b) in the list of cases for which a is equal to the scrutinee is selected, and the associated b is returned as the result. If no case matches, the default value is returned.

Literals

value :: Syntax a => Internal a -> a Source #

Literal

example :: Syntax a => a Source #

Example value

example can be used similarly to undefined in normal Haskell, i.e. to create an expression whose value is irrelevant.

Note that it is generally not possible to use undefined in Feldspar expressions, as this will crash the compiler.

Primitive functions

π :: (Floating a, PrimType a) => Data a Source #

Alias for pi

quot :: (Integral a, PrimType a) => Data a -> Data a -> Data a Source #

Integer division truncated toward zero

rem :: (Integral a, PrimType a) => Data a -> Data a -> Data a Source #

Integer remainder satisfying

(x `quot` y)*y + (x `rem` y) == x

quotRem :: (Integral a, PrimType a) => Data a -> Data a -> (Data a, Data a) Source #

Simultaneous quot and rem

div :: (Integral a, PrimType a) => Data a -> Data a -> Data a Source #

Integer division truncated toward negative infinity

mod :: (Integral a, PrimType a) => Data a -> Data a -> Data a Source #

Integer modulus, satisfying

(x `div` y)*y + (x `mod` y) == x

unsafeBalancedDiv :: (Integral a, PrimType a) => Data a -> Data a -> Data a Source #

Integer division assuming `unsafeBalancedDiv x y * y == x` (i.e. no remainder)

The advantage of using unsafeBalancedDiv over quot or div is that the above assumption can be used for simplifying the expression.

complex Source #

Arguments

:: (Num a, PrimType a, PrimType (Complex a)) 
=> Data a

Real part

-> Data a

Imaginary part

-> Data (Complex a) 

Construct a complex number

polar Source #

Arguments

:: (Floating a, PrimType a, PrimType (Complex a)) 
=> Data a

Magnitude

-> Data a

Phase

-> Data (Complex a) 

Construct a complex number

realPart :: (PrimType a, PrimType (Complex a)) => Data (Complex a) -> Data a Source #

Extract the real part of a complex number

imagPart :: (PrimType a, PrimType (Complex a)) => Data (Complex a) -> Data a Source #

Extract the imaginary part of a complex number

magnitude :: (RealFloat a, PrimType a, PrimType (Complex a)) => Data (Complex a) -> Data a Source #

Extract the magnitude of a complex number's polar form

phase :: (RealFloat a, PrimType a, PrimType (Complex a)) => Data (Complex a) -> Data a Source #

Extract the phase of a complex number's polar form

conjugate :: (RealFloat a, PrimType (Complex a)) => Data (Complex a) -> Data (Complex a) Source #

Complex conjugate

i2n :: (Integral i, Num n, PrimType i, PrimType n) => Data i -> Data n Source #

Integral type casting

i2b :: (Integral a, PrimType a) => Data a -> Data Bool Source #

Cast integer to Bool

b2i :: (Integral a, PrimType a) => Data Bool -> Data a Source #

Cast Bool to integer

round :: (RealFrac a, Num b, PrimType a, PrimType b) => Data a -> Data b Source #

Round a floating-point number to an integer

not :: Data Bool -> Data Bool Source #

Boolean negation

(&&) :: Data Bool -> Data Bool -> Data Bool infixr 3 Source #

Boolean conjunction

(||) :: Data Bool -> Data Bool -> Data Bool infixr 2 Source #

Boolean disjunction

(==) :: PrimType a => Data a -> Data a -> Data Bool infix 4 Source #

Equality

(/=) :: PrimType a => Data a -> Data a -> Data Bool infix 4 Source #

Inequality

(<) :: (Ord a, PrimType a) => Data a -> Data a -> Data Bool infix 4 Source #

Less than

(>) :: (Ord a, PrimType a) => Data a -> Data a -> Data Bool infix 4 Source #

Greater than

(<=) :: (Ord a, PrimType a) => Data a -> Data a -> Data Bool infix 4 Source #

Less than or equal

(>=) :: (Ord a, PrimType a) => Data a -> Data a -> Data Bool infix 4 Source #

Greater than or equal

min :: (Ord a, PrimType a) => Data a -> Data a -> Data a Source #

Return the smallest of two values

max :: (Ord a, PrimType a) => Data a -> Data a -> Data a Source #

Return the greatest of two values

Bit manipulation

(.&.) :: (Bits a, PrimType a) => Data a -> Data a -> Data a infixl 7 Source #

Bit-wise "and"

(.|.) :: (Bits a, PrimType a) => Data a -> Data a -> Data a infixl 5 Source #

Bit-wise "or"

xor :: (Bits a, PrimType a) => Data a -> Data a -> Data a infixl 6 Source #

Bit-wise "xor"

(⊕) :: (Bits a, PrimType a) => Data a -> Data a -> Data a Source #

Bit-wise "xor"

complement :: (Bits a, PrimType a) => Data a -> Data a Source #

Bit-wise complement

shiftL infixl 8 Source #

Arguments

:: (Bits a, PrimType a) 
=> Data a

Value to shift

-> Data Int32

Shift amount (negative value gives right shift)

-> Data a 

Left shift

shiftR infixl 8 Source #

Arguments

:: (Bits a, PrimType a) 
=> Data a

Value to shift

-> Data Int32

Shift amount (negative value gives left shift)

-> Data a 

Right shift

(.<<.) infixl 8 Source #

Arguments

:: (Bits a, PrimType a) 
=> Data a

Value to shift

-> Data Int32

Shift amount (negative value gives right shift)

-> Data a 

Left shift

(.>>.) infixl 8 Source #

Arguments

:: (Bits a, PrimType a) 
=> Data a

Value to shift

-> Data Int32

Shift amount (negative value gives left shift)

-> Data a 

Right shift

bitSize :: forall a. FiniteBits a => Data a -> Length Source #

allOnes :: (Bits a, Num a, PrimType a) => Data a Source #

Set all bits to one

oneBits :: (Bits a, Num a, PrimType a) => Data Int32 -> Data a Source #

Set the n lowest bits to one

lsbs :: (Bits a, Num a, PrimType a) => Data Int32 -> Data a -> Data a Source #

Extract the k lowest bits

ilog2 :: (FiniteBits a, Integral a, PrimType a) => Data a -> Data a Source #

Integer logarithm in base 2. Returns \(\lfloor log_2(x) \rfloor\). Assumes \(x>0\).

Arrays

arrIx :: Syntax a => IArr a -> Data Index -> a Source #

Index into an array

class Indexed a where Source #

Minimal complete definition

(!)

Associated Types

type IndexedElem a Source #

Methods

(!) :: a -> Data Index -> IndexedElem a infixl 9 Source #

Indexing operator. If a is Finite, it is assumed that i < length a in any expression a ! i.

Instances

Syntax a => Indexed (IArr a) Source # 

Associated Types

type IndexedElem (IArr a) :: * Source #

Methods

(!) :: IArr a -> Data Index -> IndexedElem (IArr a) Source #

Slicable a => Indexed (Nest a) Source # 

Associated Types

type IndexedElem (Nest a) :: * Source #

Methods

(!) :: Nest a -> Data Index -> IndexedElem (Nest a) Source #

Indexed (Pull2 a) Source #

Indexing the rows

Associated Types

type IndexedElem (Pull2 a) :: * Source #

Methods

(!) :: Pull2 a -> Data Index -> IndexedElem (Pull2 a) Source #

Indexed (Pull a) Source # 

Associated Types

type IndexedElem (Pull a) :: * Source #

Methods

(!) :: Pull a -> Data Index -> IndexedElem (Pull a) Source #

class Finite a where Source #

Linear structures with a length. If the type is also Indexed, the length is the successor of the maximal allowed index.

Minimal complete definition

length

Methods

length :: a -> Data Length Source #

The length of a finite structure

Instances

Finite (IArr a) Source # 

Methods

length :: IArr a -> Data Length Source #

Finite (Arr a) Source # 

Methods

length :: Arr a -> Data Length Source #

Finite (Nest a) Source # 

Methods

length :: Nest a -> Data Length Source #

Finite (Pull2 a) Source #

length gives number of rows

Methods

length :: Pull2 a -> Data Length Source #

Finite (Pull a) Source # 

Methods

length :: Pull a -> Data Length Source #

Finite (Push2 m a) Source #

length gives number of rows

Methods

length :: Push2 m a -> Data Length Source #

Finite (Push m a) Source # 

Methods

length :: Push m a -> Data Length Source #

class Slicable a where Source #

Linear structures that can be sliced

Minimal complete definition

slice

Methods

slice :: Data Index -> Data Length -> a -> a Source #

Take a slice of a structure

Instances

Slicable (IArr a) Source # 

Methods

slice :: Data Index -> Data Length -> IArr a -> IArr a Source #

Slicable (Arr a) Source # 

Methods

slice :: Data Index -> Data Length -> Arr a -> Arr a Source #

Slicable a => Slicable (Nest a) Source # 

Methods

slice :: Data Index -> Data Length -> Nest a -> Nest a Source #

Slicable (Pull2 a) Source #

Take a slice of the rows

Methods

slice :: Data Index -> Data Length -> Pull2 a -> Pull2 a Source #

Slicable (Pull a) Source # 

Methods

slice :: Data Index -> Data Length -> Pull a -> Pull a Source #

Syntactic conversion

desugar :: Syntax a => a -> Data (Internal a) Source #

sugar :: Syntax a => Data (Internal a) -> a Source #

resugar :: (Syntax a, Syntax b, Internal a ~ Internal b) => a -> b Source #

Cast between two values that have the same syntactic representation

Assertions

guardVal Source #

Arguments

:: Syntax a 
=> Data Bool

Condition that is expected to be true

-> String

Error message

-> a

Value to attach the assertion to

-> a 

Guard a value by an assertion (with implicit label UserAssertion "")

guardValLabel Source #

Arguments

:: Syntax a 
=> AssertionLabel

Assertion label

-> Data Bool

Condition that is expected to be true

-> String

Error message

-> a

Value to attach the assertion to

-> a 

Like guardVal but with an explicit assertion label

Unsafe operations

unsafePerform :: Syntax a => Comp a -> a Source #

Turn a Comp computation into a pure value. For this to be safe, the computation should be free of side effects and independent of its environment.

Programs with computational effects

class Monad m => MonadComp m where Source #

Monads that support computational effects: mutable data structures and control flow

Minimal complete definition

liftComp, iff, for, while

Methods

liftComp :: Comp a -> m a Source #

Lift a Comp computation

iff :: Data Bool -> m () -> m () -> m () Source #

Conditional statement

for :: (Integral n, PrimType n) => IxRange (Data n) -> (Data n -> m ()) -> m () Source #

For loop

while :: m (Data Bool) -> m () -> m () Source #

While loop

Instances

MonadComp Comp Source # 

Methods

liftComp :: Comp a -> Comp a Source #

iff :: Data Bool -> Comp () -> Comp () -> Comp () Source #

for :: (Integral n, PrimType n) => IxRange (Data n) -> (Data n -> Comp ()) -> Comp () Source #

while :: Comp (Data Bool) -> Comp () -> Comp () Source #

MonadComp Run Source # 

Methods

liftComp :: Comp a -> Run a Source #

iff :: Data Bool -> Run () -> Run () -> Run () Source #

for :: (Integral n, PrimType n) => IxRange (Data n) -> (Data n -> Run ()) -> Run () Source #

while :: Run (Data Bool) -> Run () -> Run () Source #

MonadComp m => MonadComp (OptionT m) Source # 

Methods

liftComp :: Comp a -> OptionT m a Source #

iff :: Data Bool -> OptionT m () -> OptionT m () -> OptionT m () Source #

for :: (Integral n, PrimType n) => IxRange (Data n) -> (Data n -> OptionT m ()) -> OptionT m () Source #

while :: OptionT m (Data Bool) -> OptionT m () -> OptionT m () Source #

References

newRef :: (Syntax a, MonadComp m) => m (Ref a) Source #

Create an uninitialized reference

newNamedRef Source #

Arguments

:: (Syntax a, MonadComp m) 
=> String

Base name

-> m (Ref a) 

Create an uninitialized named reference

The provided base name may be appended with a unique identifier to avoid name collisions.

initRef :: (Syntax a, MonadComp m) => a -> m (Ref a) Source #

Create an initialized named reference

initNamedRef Source #

Arguments

:: (Syntax a, MonadComp m) 
=> String

Base name

-> a

Initial value

-> m (Ref a) 

Create an initialized reference

The provided base name may be appended with a unique identifier to avoid name collisions.

getRef :: (Syntax a, MonadComp m) => Ref a -> m a Source #

Get the contents of a reference.

setRef :: (Syntax a, MonadComp m) => Ref a -> a -> m () Source #

Set the contents of a reference.

modifyRef :: (Syntax a, MonadComp m) => Ref a -> (a -> a) -> m () Source #

Modify the contents of reference.

unsafeFreezeRef :: (Syntax a, MonadComp m) => Ref a -> m a Source #

Freeze the contents of reference (only safe if the reference is not updated as long as the resulting value is alive).

Arrays

newArr :: (Type (Internal a), MonadComp m) => Data Length -> m (Arr a) Source #

Create an uninitialized array

newNamedArr Source #

Arguments

:: (Type (Internal a), MonadComp m) 
=> String

Base name

-> Data Length 
-> m (Arr a) 

Create an uninitialized named array

The provided base name may be appended with a unique identifier to avoid name collisions.

constArr Source #

Arguments

:: (PrimType (Internal a), MonadComp m) 
=> [Internal a]

Initial contents

-> m (Arr a) 

Create an array and initialize it with a constant list

constNamedArr Source #

Arguments

:: (PrimType (Internal a), MonadComp m) 
=> String

Base name

-> [Internal a]

Initial contents

-> m (Arr a) 

Create a named array and initialize it with a constant list

The provided base name may be appended with a unique identifier to avoid name collisions.

getArr :: (Syntax a, MonadComp m) => Arr a -> Data Index -> m a Source #

Get an element of an array

setArr :: forall m a. (Syntax a, MonadComp m) => Arr a -> Data Index -> a -> m () Source #

Set an element of an array

copyArr Source #

Arguments

:: MonadComp m 
=> Arr a

Destination

-> Arr a

Source

-> m () 

Copy the contents of an array to another array. The length of the destination array must not be less than that of the source array.

In order to copy only a part of an array, use slice before calling copyArr.

freezeArr :: (Type (Internal a), MonadComp m) => Arr a -> m (IArr a) Source #

Freeze a mutable array to an immutable one. This involves copying the array to a newly allocated one.

freezeSlice :: (Type (Internal a), MonadComp m) => Data Length -> Arr a -> m (IArr a) Source #

A version of freezeArr that slices the array from 0 to the given length

unsafeFreezeArr :: MonadComp m => Arr a -> m (IArr a) Source #

Freeze a mutable array to an immutable one without making a copy. This is generally only safe if the the mutable array is not updated as long as the immutable array is alive.

unsafeFreezeSlice :: MonadComp m => Data Length -> Arr a -> m (IArr a) Source #

A version of unsafeFreezeArr that slices the array from 0 to the given length

thawArr :: (Type (Internal a), MonadComp m) => IArr a -> m (Arr a) Source #

Thaw an immutable array to a mutable one. This involves copying the array to a newly allocated one.

unsafeThawArr :: MonadComp m => IArr a -> m (Arr a) Source #

Thaw an immutable array to a mutable one without making a copy. This is generally only safe if the the mutable array is not updated as long as the immutable array is alive.

constIArr :: (PrimType (Internal a), MonadComp m) => [Internal a] -> m (IArr a) Source #

Create an immutable array and initialize it with a constant list

Control-flow

ifE Source #

Arguments

:: (Syntax a, MonadComp m) 
=> Data Bool

Condition

-> m a

True branch

-> m a

False branch

-> m a 

Conditional statement that returns an expression

break :: MonadComp m => m () Source #

Break out from a loop

assert Source #

Arguments

:: MonadComp m 
=> Data Bool

Expression that should be true

-> String

Message in case of failure

-> m () 

Assertion (with implicit label UserAssertion "")

assertLabel Source #

Arguments

:: MonadComp m 
=> AssertionLabel

Assertion label

-> Data Bool

Expression that should be true

-> String

Message in case of failure

-> m () 

Like assert but tagged with an explicit assertion label

Misc.

shareM :: (Syntax a, MonadComp m) => a -> m a Source #

Force evaluation of a value and share the result (monadic version of share)

Orphan instances

Syntactic () Source # 

Associated Types

type Domain () :: * -> * #

type Internal () :: * #

Methods

desugar :: () -> ASTF (Domain ()) (Internal ()) #

sugar :: ASTF (Domain ()) (Internal ()) -> () #

(Bounded a, Type a) => Bounded (Data a) Source # 

Methods

minBound :: Data a #

maxBound :: Data a #

(Floating a, PrimType a) => Floating (Data a) Source # 

Methods

pi :: Data a #

exp :: Data a -> Data a #

log :: Data a -> Data a #

sqrt :: Data a -> Data a #

(**) :: Data a -> Data a -> Data a #

logBase :: Data a -> Data a -> Data a #

sin :: Data a -> Data a #

cos :: Data a -> Data a #

tan :: Data a -> Data a #

asin :: Data a -> Data a #

acos :: Data a -> Data a #

atan :: Data a -> Data a #

sinh :: Data a -> Data a #

cosh :: Data a -> Data a #

tanh :: Data a -> Data a #

asinh :: Data a -> Data a #

acosh :: Data a -> Data a #

atanh :: Data a -> Data a #

log1p :: Data a -> Data a #

expm1 :: Data a -> Data a #

log1pexp :: Data a -> Data a #

log1mexp :: Data a -> Data a #

(Fractional a, PrimType a) => Fractional (Data a) Source # 

Methods

(/) :: Data a -> Data a -> Data a #

recip :: Data a -> Data a #

fromRational :: Rational -> Data a #

(Num a, PrimType a) => Num (Data a) Source # 

Methods

(+) :: Data a -> Data a -> Data a #

(-) :: Data a -> Data a -> Data a #

(*) :: Data a -> Data a -> Data a #

negate :: Data a -> Data a #

abs :: Data a -> Data a #

signum :: Data a -> Data a #

fromInteger :: Integer -> Data a #