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

Safe HaskellNone

Data.Array.Knead.Simple.Symbolic

Synopsis

Documentation

data Array sh a Source

Instances

C Array 
(C sh, MV sh, C a) => Argument (Array sh a) 
(MV sh, C sh, C a) => C (Array sh a) 

class C array whereSource

This class allows to implement functions without parameters for both simple and parameterized arrays.

Methods

lift0 :: Array sh a -> array sh aSource

lift1 :: (Array sha a -> Array shb b) -> array sha a -> array shb bSource

lift2 :: (Array sha a -> Array shb b -> Array shc c) -> array sha a -> array shb b -> array shc cSource

Instances

C Array 
C (Array p) 

data Exp a

Instances

Value Exp 
(Transcendental a, Real a, RationalConstant a) => Floating (Exp a) 
(Field a, Real a, RationalConstant a) => Fractional (Exp a) 
(PseudoRing a, Real a, IntegerConstant a) => Num (Exp a) 
Compose (Exp a) 
(Transcendental a, RationalConstant a) => C (Exp a) 
(Transcendental a, RationalConstant a) => C (Exp a) 
(Field a, RationalConstant a) => C (Exp a) 
(Real a, PseudoRing a, IntegerConstant a) => C (Exp a) 
(PseudoRing a, IntegerConstant a) => C (Exp a) 
Additive a => C (Exp a)

We do not require a numeric prelude superclass, thus also LLVM only types like vectors are instances.

MV a => Argument (Exp a) 
(C a, C a) => C (Exp a) 
(~ * a (Scalar v), PseudoModule v, IntegerConstant a) => C (Exp a) (Exp v) 

fix :: Id (Array sh a)Source

shape :: Array sh a -> Exp shSource

(!) :: (C sh, Index sh ~ ix) => Array sh a -> Exp ix -> Exp aSource

the :: Scalar sh => Array sh a -> Exp aSource

fromScalar :: Scalar sh => Exp a -> Array sh aSource

fill :: Exp sh -> Exp a -> Array sh aSource

gather :: (C array, C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C a) => array sh1 ix0 -> array sh0 a -> array sh1 aSource

backpermute :: (C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C a) => Exp sh1 -> (Exp ix1 -> Exp ix0) -> Array sh0 a -> Array sh1 aSource

backpermute2 :: (C array, C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C sh, Index sh ~ ix) => Exp sh -> (Exp ix -> Exp ix0) -> (Exp ix -> Exp ix1) -> (Exp a -> Exp b -> Exp c) -> array sh0 a -> array sh1 b -> array sh cSource

id :: (C array, C sh, Index sh ~ ix) => Exp sh -> array sh ixSource

map :: (C array, C sh) => (Exp a -> Exp b) -> array sh a -> array sh bSource

mapWithIndex :: (C array, C sh, Index sh ~ ix) => (Exp ix -> Exp a -> Exp b) -> array sh a -> array sh bSource

zipWith :: (C array, C sh) => (Exp a -> Exp b -> Exp c) -> array sh a -> array sh b -> array sh cSource

zipWith3 :: (C array, C sh) => (Exp a -> Exp b -> Exp c -> Exp d) -> array sh a -> array sh b -> array sh c -> array sh dSource

zipWith4 :: (C array, C sh) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> array sh a -> array sh b -> array sh c -> array sh d -> array sh eSource

zip :: (C array, C sh) => array sh a -> array sh b -> array sh (a, b)Source

zip3 :: (C array, C sh) => array sh a -> array sh b -> array sh c -> array sh (a, b, c)Source

zip4 :: (C array, C sh) => array sh a -> array sh b -> array sh c -> array sh d -> array sh (a, b, c, d)Source

fold1 :: (C array, C sh0, C sh1, C a) => (Exp a -> Exp a -> Exp a) -> array (sh0, sh1) a -> array sh0 aSource

fold1All :: (C sh, C a) => (Exp a -> Exp a -> Exp a) -> Array sh a -> Exp aSource

findAll :: (C sh, C a) => (Exp a -> Exp Bool) -> Array sh a -> Exp (Maybe a)Source

In principle this can be implemented using fold1All but it has a short-cut semantics. All means that it scans all dimensions but it does not mean that it finds all occurrences. If you want to get the index of the found element, please decorate the array elements with their indices before calling findAll.