knead-0.4.2: Repa-like array processing using LLVM JIT

Safe HaskellNone

Data.Array.Knead.Expression

Synopsis

Documentation

newtype Exp a Source

Constructors

Exp 

Fields

unExp :: forall r. CodeGenFunction r (T a)
 

Instances

Value Exp 
(Field a, Real a, RationalConstant a) => Fractional (Exp a) 
(PseudoRing a, Real a, IntegerConstant a) => Num (Exp a) 
Compose (Exp a) 
(C a, Storable a) => Argument (Exp a) 
(C a, Storable a) => C (Exp a) 

class Value val whereSource

Methods

lift0 :: T a -> val aSource

lift1 :: (T a -> T b) -> val a -> val bSource

lift2 :: (T a -> T b -> T c) -> val a -> val b -> val cSource

lift3 :: (T a -> T b -> T c -> T d) -> val a -> val b -> val c -> val dSource

lift4 :: (T a -> T b -> T c -> T d -> T e) -> val a -> val b -> val c -> val d -> val eSource

Instances

liftM :: (forall r. T a -> CodeGenFunction r (T b)) -> Exp a -> Exp bSource

liftM2 :: (forall r. T a -> T b -> CodeGenFunction r (T c)) -> Exp a -> Exp b -> Exp cSource

liftM3 :: (forall r. T a -> T b -> T c -> CodeGenFunction r (T d)) -> Exp a -> Exp b -> Exp c -> Exp dSource

unliftM1 :: (Exp a -> Exp b) -> T a -> CodeGenFunction r (T b)Source

unliftM2 :: (Exp a -> Exp b -> Exp c) -> T a -> T b -> CodeGenFunction r (T c)Source

unliftM3 :: (Exp a -> Exp b -> Exp c -> Exp d) -> T a -> T b -> T c -> CodeGenFunction r (T d)Source

zip :: Value val => val a -> val b -> val (a, b)Source

zip3 :: Value val => val a -> val b -> val c -> val (a, b, c)Source

zip4 :: Value val => val a -> val b -> val c -> val d -> val (a, b, c, d)Source

unzip :: Value val => val (a, b) -> (val a, val b)Source

unzip3 :: Value val => val (a, b, c) -> (val a, val b, val c)Source

unzip4 :: Value val => val (a, b, c, d) -> (val a, val b, val c, val d)Source

fst :: Value val => val (a, b) -> val aSource

snd :: Value val => val (a, b) -> val bSource

mapFst :: (Exp a -> Exp b) -> Exp (a, c) -> Exp (b, c)Source

mapSnd :: (Exp b -> Exp c) -> Exp (a, b) -> Exp (a, c)Source

swap :: Value val => val (a, b) -> val (b, a)Source

curry :: (Exp (a, b) -> c) -> Exp a -> Exp b -> cSource

uncurry :: (Exp a -> Exp b -> c) -> Exp (a, b) -> cSource

fst3 :: Value val => val (a, b, c) -> val aSource

snd3 :: Value val => val (a, b, c) -> val bSource

thd3 :: Value val => val (a, b, c) -> val cSource

mapFst3 :: (Exp a0 -> Exp a1) -> Exp (a0, b, c) -> Exp (a1, b, c)Source

mapSnd3 :: (Exp b0 -> Exp b1) -> Exp (a, b0, c) -> Exp (a, b1, c)Source

mapThd3 :: (Exp c0 -> Exp c1) -> Exp (a, b, c0) -> Exp (a, b, c1)Source

modifyMultiValue :: (Value val, Compose a, Decompose pattern, PatternTuple pattern ~ tuple) => pattern -> (Decomposed T pattern -> a) -> val tuple -> val (Composed a)Source

modifyMultiValue2 :: (Value val, Compose a, Decompose patternA, Decompose patternB, PatternTuple patternA ~ tupleA, PatternTuple patternB ~ tupleB) => patternA -> patternB -> (Decomposed T patternA -> Decomposed T patternB -> a) -> val tupleA -> val tupleB -> val (Composed a)Source

modifyMultiValueM :: (Compose a, Decompose pattern, PatternTuple pattern ~ tuple) => pattern -> (forall r. Decomposed T pattern -> CodeGenFunction r a) -> Exp tuple -> Exp (Composed a)Source

modifyMultiValueM2 :: (Compose a, Decompose patternA, Decompose patternB, PatternTuple patternA ~ tupleA, PatternTuple patternB ~ tupleB) => patternA -> patternB -> (forall r. Decomposed T patternA -> Decomposed T patternB -> CodeGenFunction r a) -> Exp tupleA -> Exp tupleB -> Exp (Composed a)Source

class Compose multituple whereSource

Associated Types

type Composed multituple Source

Methods

compose :: multituple -> Exp (Composed multituple)Source

A nested zip.

Instances

Compose () 
Compose a => Compose (Complex a) 
Compose n => Compose (ZeroBased n) 
(Enum enum, Bounded enum) => Compose (Enumeration enum) 
Compose (Exp a) 
(Compose a, Compose b) => Compose (a, b) 
(Compose sh, ~ * (Composed sh) (T (Tag (Composed sh)) (Unwrap (Composed sh))), Compose s) => Compose (:. sh s) 
(Compose a, Compose b, Compose c) => Compose (a, b, c) 
(Compose a, Compose b, Compose c, Compose d) => Compose (a, b, c, d) 

class Composed (Decomposed Exp pattern) ~ PatternTuple pattern => Decompose pattern whereSource

Methods

decompose :: pattern -> Exp (PatternTuple pattern) -> Decomposed Exp patternSource

Analogous to decompose.

Instances

Decompose () 
Decompose p => Decompose (Complex p) 
Decompose pn => Decompose (ZeroBased pn) 
Decompose (Enumeration enum) 
Decompose (Atom a) 
(Decompose pa, Decompose pb) => Decompose (pa, pb) 
Decompose tag sh => Decompose (T tag sh) 
(Decompose pa, Decompose pb, Decompose pc) => Decompose (pa, pb, pc) 
(Decompose pa, Decompose pb, Decompose pc, Decompose pd) => Decompose (pa, pb, pc, pd) 

modify :: (Compose a, Decompose pattern) => pattern -> (Decomposed Exp pattern -> a) -> Exp (PatternTuple pattern) -> Exp (Composed a)Source

Analogus to modifyMultiValue.

modify2 :: (Compose a, Decompose patternA, Decompose patternB) => patternA -> patternB -> (Decomposed Exp patternA -> Decomposed Exp patternB -> a) -> Exp (PatternTuple patternA) -> Exp (PatternTuple patternB) -> Exp (Composed a)Source

consComplex :: Exp a -> Exp a -> Exp (Complex a)Source

You can construct complex numbers this way, but they will not make you happy, because the numeric operations require a RealFloat instance that we could only provide with lots of undefined methods (also in its superclasses). You may either define your own arithmetic or use the NumericPrelude type classes.

cons :: C a => a -> Exp aSource

zero :: C a => Exp aSource

add :: Additive a => Exp a -> Exp a -> Exp aSource

sub :: Additive a => Exp a -> Exp a -> Exp aSource

mul :: PseudoRing a => Exp a -> Exp a -> Exp aSource

sqr :: PseudoRing a => Exp a -> Exp aSource

sqrt :: Algebraic a => Exp a -> Exp aSource

idiv :: Integral a => Exp a -> Exp a -> Exp aSource

irem :: Integral a => Exp a -> Exp a -> Exp aSource

shl :: BitShift a => Exp a -> Exp a -> Exp aSource

shr :: BitShift a => Exp a -> Exp a -> Exp aSource

fromFastMath :: Exp (Number flags a) -> Exp aSource

toFastMath :: Exp a -> Exp (Number flags a)Source

(==*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

(<=*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

(>*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

(>=*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

(<*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

(/=*) :: Comparison a => Exp a -> Exp a -> Exp BoolSource

min :: Real a => Exp a -> Exp a -> Exp aSource

max :: Real a => Exp a -> Exp a -> Exp aSource

select :: Select a => Exp Bool -> Exp a -> Exp a -> Exp aSource

Like ifThenElse but computes both alternative expressions and then uses LLVM's efficient select instruction.

ifThenElse :: C a => Exp Bool -> Exp a -> Exp a -> Exp aSource

complement :: Logic a => Exp a -> Exp aSource

(.&.*) :: Logic a => Exp a -> Exp a -> Exp aSource

(.|.*) :: Logic a => Exp a -> Exp a -> Exp aSource

xor :: Logic a => Exp a -> Exp a -> Exp aSource

maybe :: C b => Exp b -> (Exp a -> Exp b) -> Exp (Maybe a) -> Exp bSource