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

Safe HaskellNone

Data.Array.Knead.Shape.Cubic

Documentation

class C ix whereSource

Methods

switch :: f Z -> (forall ix0 i. (C ix0, Single i) => f (ix0 :. i)) -> f ixSource

Instances

C Z 
(C ix0, Single i) => C (:. ix0 i) 

switchInt :: C ix => f Z -> (forall ix0. C ix0 => f (ix0 :. Int)) -> f ixSource

intersect :: C sh => Exp (Shape sh) -> Exp (Shape sh) -> Exp (Shape sh)Source

value :: (C sh, Value val) => T tag sh -> val (T tag sh)Source

constant :: (C sh, Value val) => val Int -> val (T tag sh)Source

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

tunnel :: C sh => T p (T tag sh) -> Tunnel p (T tag sh)Source

flattenIndex :: C sh => T (Shape sh) -> T (Index sh) -> CodeGenFunction r (Value Size)Source

peek :: C sh => Ptr Size -> IO shSource

poke :: C sh => Ptr Size -> sh -> IO ()Source

type family Struct sh Source

newtype T tag sh Source

Constructors

Cons 

Fields

decons :: sh
 

Instances

C sh => Storable (T tag sh) 
(C sh, StructFields (Struct sh)) => C (T tag sh) 
C sh => C (T tag sh) 
Decompose tag sh => Decompose (T tag sh) 
(~ * tag ShapeTag, ~ * sh Z) => Scalar (T tag sh) 
(~ * tag ShapeTag, C sh) => C (T tag sh) 

data Z Source

Constructors

Z 

Instances

Eq Z 
Ord Z 
Read Z 
Show Z 
C Z 

z :: Value val => val (T tag Z)Source

data tail :. head Source

Constructors

!tail :. !head 

Instances

(Decompose tag sh, Decompose s) => Decompose tag (:. sh s) 
(Eq tail, Eq head) => Eq (:. tail head) 
(Ord tail, Ord head) => Ord (:. tail head) 
(Read tail, Read head) => Read (:. tail head) 
(Show tail, Show head) => Show (:. tail head) 
(Compose sh, ~ * (Composed sh) (T (Tag (Composed sh)) (Unwrap (Composed sh))), Compose s) => Compose (:. sh s) 
(C ix0, Single i) => C (:. ix0 i) 

type Shape = T ShapeTagSource

shape :: sh -> Shape shSource

type Index = T IndexTagSource

index :: ix -> Index ixSource

cons :: Value val => val (T tag sh) -> val i -> val (T tag (sh :. i))Source

(#:.) :: Value val => val (T tag sh) -> val i -> val (T tag (sh :. i))Source

head :: Value val => val (T tag (sh :. i)) -> val iSource

tail :: Value val => val (T tag (sh :. i)) -> val (T tag sh)Source

switchR :: Value val => (val (T tag sh) -> val i -> a) -> val (T tag (sh :. i)) -> aSource

loadMultiValue :: C sh => Value (Ptr (Struct (Struct sh))) -> CodeGenFunction r (T (T tag sh))Source

storeMultiValue :: C sh => T (T tag sh) -> Value (Ptr (Struct (Struct sh))) -> CodeGenFunction r ()Source