knead-0.2: Repa array processing using LLVM JIT

Safe HaskellNone

Data.Array.Knead.Index.Nested.Shape

Documentation

value :: (C sh, Value val) => sh -> val shSource

paramWith :: (Storable b, C b, Value val) => T p b -> (forall parameters. (Storable parameters, C parameters) => (p -> parameters) -> (T parameters -> val b) -> a) -> aSource

load :: C sh => f sh -> Value (Ptr (Struct sh)) -> CodeGenFunction r (T sh)Source

intersect :: C sh => Exp sh -> Exp sh -> Exp shSource

class C sh => C sh whereSource

Associated Types

type Index sh :: *Source

Methods

intersectCode :: T sh -> T sh -> CodeGenFunction r (T sh)Source

sizeCode :: T sh -> CodeGenFunction r (Value Word32)Source

size :: sh -> IntSource

flattenIndexRec :: T sh -> T (Index sh) -> CodeGenFunction r (Value Word32, Value Word32)Source

Result is (size, flattenedIndex). size must equal the result of sizeCode. We use this for sharing intermediate results.

loop :: (Index sh ~ ix, Phi state) => (T ix -> state -> CodeGenFunction r state) -> T sh -> state -> CodeGenFunction r stateSource

Instances

C Word32 
C Word64 
C () 
(C n, C m) => C (n, m) 
(~ * tag ShapeTag, C sh) => C (T tag sh) 
(C n, C m, C l) => C (n, m, l) 

class C sh => Scalar sh whereSource

Methods

scalar :: Value val => val shSource

zeroIndex :: Value val => f sh -> val (Index sh)Source

Instances

Scalar () 

loopPrimitive :: (Repr Value i ~ Value i, Num i, IsConst i, IsInteger i, CmpRet i, CmpResult i ~ Bool, Phi state) => (T i -> state -> CodeGenFunction r state) -> T i -> state -> CodeGenFunction r stateSource