yarr-1.4.0.2: Yet another array library

Safe HaskellNone
LanguageHaskell98

Data.Yarr.Repr.Foreign

Synopsis

Documentation

data F Source #

Foreign representation is the heart of Yarr framework.

Internally it holds raw pointer (Ptr), which makes indexing foreign arrays not slower than GHC's built-in primitive arrays, but without freeze/thaw boilerplate.

Foreign arrays are very permissible, for example you can easily use them as source and target of Loading operation simultaneously, achieving old good in-place C-style array modifying:

loadS fill (dmap sqrt arr) arr

Foreign arrays are intented to hold all Storable types and vectors of them (because there is a conditional instance of Storalbe class for Vectors of Storables too).

Instances

(Shape sh, Storable a) => UTarget F L sh a Source # 

Methods

write :: UArray F L sh a -> sh -> a -> IO () Source #

linearWrite :: UArray F L sh a -> Int -> a -> IO () Source #

(Shape sh, Storable a) => USource F L sh a Source # 

Methods

index :: UArray F L sh a -> sh -> IO a Source #

linearIndex :: UArray F L sh a -> Int -> IO a Source #

Shape sh => Regular F L sh a Source # 

Associated Types

data UArray F L sh a :: * Source #

Methods

extent :: UArray F L sh a -> sh Source #

touchArray :: UArray F L sh a -> IO () Source #

force :: UArray F L sh a -> IO () Source #

DefaultFusion F D L sh Source # 

Methods

dmap :: (USource F L sh a, USource D L sh b) => (a -> b) -> UArray F L sh a -> UArray D L sh b Source #

dmapM :: (USource F L sh a, USource D L sh b) => (a -> IO b) -> UArray F L sh a -> UArray D L sh b Source #

dzip2 :: (USource F L sh a, USource F L sh b, USource D L sh c) => (a -> b -> c) -> UArray F L sh a -> UArray F L sh b -> UArray D L sh c Source #

dzip2M :: (USource F L sh a, USource F L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray F L sh a -> UArray F L sh b -> UArray D L sh c Source #

dzip3 :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D L sh d Source #

dzip3M :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D L sh d Source #

dzip :: (USource F L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray F L sh a) -> UArray D L sh b Source #

dzipM :: (USource F L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray F L sh a) -> UArray D L sh b Source #

(Shape sh, Storable a) => Manifest F F L sh a Source # 

Methods

new :: sh -> IO (UArray F L sh a) Source #

freeze :: UArray F L sh a -> IO (UArray F L sh a) Source #

thaw :: UArray F L sh a -> IO (UArray F L sh a) Source #

Shape sh => DefaultIFusion F L D SH sh Source # 

Methods

imap :: (USource F L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray F L sh a -> UArray D SH sh b Source #

imapM :: (USource F L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray F L sh a -> UArray D SH sh b Source #

izip2 :: (USource F L sh a, USource F L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray F L sh a -> UArray F L sh b -> UArray D SH sh c Source #

izip2M :: (USource F L sh a, USource F L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray F L sh a -> UArray F L sh b -> UArray D SH sh c Source #

izip3 :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D SH sh d Source #

izip3M :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D SH sh d Source #

izip :: (USource F L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray F L sh a) -> UArray D SH sh b Source #

izipM :: (USource F L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray F L sh a) -> UArray D SH sh b Source #

(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecTarget F FS L sh v e Source # 
(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecSource F FS L sh v e Source # 
(Shape sh, Vector v e, Storable e, Storable (v e)) => VecRegular F FS L sh v e Source # 

Methods

slices :: UArray F L sh (v e) -> VecList (Dim v) (UArray FS L sh e) Source #

(Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e Source # 
Shape sh => NFData (UArray F L sh a) Source # 

Methods

rnf :: UArray F L sh a -> () #

data UArray F L Source # 
data UArray F L = ForeignArray !sh !(ForeignPtr a) !(Ptr a)

data FS Source #

Foreign Slice representation, view slice representation for Foreign arrays.

To understand Foreign Slices, suppose you have standard image array of UArray F Dim2 (VecList N3 Word8) type.

It's layout in memory (with array indices):

 r g b | r g b | r g b | ...
(0, 0)  (0, 1)  (0, 2)   ...
let (VecList [reds, greens, blues]) = slices image
-- reds, greens, blues :: UArray FS Dim2 Word8

Now blues just indexes each third byte on the same underlying memory block:

... b | ... b | ... b | ...
  (0, 0)  (0, 1)  (0, 2)...

Instances

(Shape sh, Storable e) => UTarget FS L sh e Source # 

Methods

write :: UArray FS L sh e -> sh -> e -> IO () Source #

linearWrite :: UArray FS L sh e -> Int -> e -> IO () Source #

(Shape sh, Storable e) => USource FS L sh e Source # 

Methods

index :: UArray FS L sh e -> sh -> IO e Source #

linearIndex :: UArray FS L sh e -> Int -> IO e Source #

Shape sh => Regular FS L sh e Source # 

Associated Types

data UArray FS L sh e :: * Source #

Methods

extent :: UArray FS L sh e -> sh Source #

touchArray :: UArray FS L sh e -> IO () Source #

force :: UArray FS L sh e -> IO () Source #

DefaultFusion FS D L sh Source # 

Methods

dmap :: (USource FS L sh a, USource D L sh b) => (a -> b) -> UArray FS L sh a -> UArray D L sh b Source #

dmapM :: (USource FS L sh a, USource D L sh b) => (a -> IO b) -> UArray FS L sh a -> UArray D L sh b Source #

dzip2 :: (USource FS L sh a, USource FS L sh b, USource D L sh c) => (a -> b -> c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D L sh c Source #

dzip2M :: (USource FS L sh a, USource FS L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D L sh c Source #

dzip3 :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D L sh d Source #

dzip3M :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D L sh d Source #

dzip :: (USource FS L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray FS L sh a) -> UArray D L sh b Source #

dzipM :: (USource FS L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray FS L sh a) -> UArray D L sh b Source #

Shape sh => DefaultIFusion FS L D SH sh Source # 

Methods

imap :: (USource FS L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray FS L sh a -> UArray D SH sh b Source #

imapM :: (USource FS L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray FS L sh a -> UArray D SH sh b Source #

izip2 :: (USource FS L sh a, USource FS L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D SH sh c Source #

izip2M :: (USource FS L sh a, USource FS L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D SH sh c Source #

izip3 :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D SH sh d Source #

izip3M :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D SH sh d Source #

izip :: (USource FS L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray FS L sh a) -> UArray D SH sh b Source #

izipM :: (USource FS L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray FS L sh a) -> UArray D SH sh b Source #

(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecTarget F FS L sh v e Source # 
(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecSource F FS L sh v e Source # 
(Shape sh, Vector v e, Storable e, Storable (v e)) => VecRegular F FS L sh v e Source # 

Methods

slices :: UArray F L sh (v e) -> VecList (Dim v) (UArray FS L sh e) Source #

Shape sh => NFData (UArray FS L sh e) Source # 

Methods

rnf :: UArray FS L sh e -> () #

data UArray FS L Source # 
data UArray FS L = ForeignSlice !sh !Int !(ForeignPtr e) !(Ptr e)

There are also ForeignArray and ForeignSlice UArray family constructors, which aren't presented in the docs because Haddock doesn't support associated family constructors.

See source of Data.Yarr.Repr.Foreign module.

class Storable a #

The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.

Memory addresses are represented as values of type Ptr a, for some a which is an instance of class Storable. The type argument to Ptr helps provide some valuable type safety in FFI code (you can't mix pointers of different types without an explicit cast), while helping the Haskell type system figure out which marshalling method is needed for a given pointer.

All marshalling between Haskell and a foreign language ultimately boils down to translating Haskell data structures into the binary representation of a corresponding data structure of the foreign language and vice versa. To code this marshalling in Haskell, it is necessary to manipulate primitive data types stored in unstructured memory blocks. The class Storable facilitates this manipulation on all types for which it is instantiated, which are the standard basic types of Haskell, the fixed size Int types (Int8, Int16, Int32, Int64), the fixed size Word types (Word8, Word16, Word32, Word64), StablePtr, all types from Foreign.C.Types, as well as Ptr.

Minimal complete definition

sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Instances

Storable Bool 

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Storable Char 

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Storable Double 
Storable Float 

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Storable Int 

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

pokeElemOff :: Ptr Int -> Int -> Int -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int #

pokeByteOff :: Ptr b -> Int -> Int -> IO () #

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Storable Int8 

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Storable Int16 

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Storable Int32 

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Storable Int64 

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Storable Word 

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Storable Word8 

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Storable Word16 
Storable Word32 
Storable Word64 
Storable () 

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

peekElemOff :: Ptr () -> Int -> IO () #

pokeElemOff :: Ptr () -> Int -> () -> IO () #

peekByteOff :: Ptr b -> Int -> IO () #

pokeByteOff :: Ptr b -> Int -> () -> IO () #

peek :: Ptr () -> IO () #

poke :: Ptr () -> () -> IO () #

Storable CChar 

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

pokeElemOff :: Ptr CChar -> Int -> CChar -> IO () #

peekByteOff :: Ptr b -> Int -> IO CChar #

pokeByteOff :: Ptr b -> Int -> CChar -> IO () #

peek :: Ptr CChar -> IO CChar #

poke :: Ptr CChar -> CChar -> IO () #

Storable CSChar 
Storable CUChar 
Storable CShort 
Storable CUShort 
Storable CInt 

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

pokeElemOff :: Ptr CInt -> Int -> CInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CInt #

pokeByteOff :: Ptr b -> Int -> CInt -> IO () #

peek :: Ptr CInt -> IO CInt #

poke :: Ptr CInt -> CInt -> IO () #

Storable CUInt 

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

pokeElemOff :: Ptr CUInt -> Int -> CUInt -> IO () #

peekByteOff :: Ptr b -> Int -> IO CUInt #

pokeByteOff :: Ptr b -> Int -> CUInt -> IO () #

peek :: Ptr CUInt -> IO CUInt #

poke :: Ptr CUInt -> CUInt -> IO () #

Storable CLong 

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

pokeElemOff :: Ptr CLong -> Int -> CLong -> IO () #

peekByteOff :: Ptr b -> Int -> IO CLong #

pokeByteOff :: Ptr b -> Int -> CLong -> IO () #

peek :: Ptr CLong -> IO CLong #

poke :: Ptr CLong -> CLong -> IO () #

Storable CULong 
Storable CLLong 
Storable CULLong 
Storable CFloat 
Storable CDouble 
Storable CPtrdiff 
Storable CSize 

Methods

sizeOf :: CSize -> Int #

alignment :: CSize -> Int #

peekElemOff :: Ptr CSize -> Int -> IO CSize #

pokeElemOff :: Ptr CSize -> Int -> CSize -> IO () #

peekByteOff :: Ptr b -> Int -> IO CSize #

pokeByteOff :: Ptr b -> Int -> CSize -> IO () #

peek :: Ptr CSize -> IO CSize #

poke :: Ptr CSize -> CSize -> IO () #

Storable CWchar 
Storable CSigAtomic 
Storable CClock 
Storable CTime 

Methods

sizeOf :: CTime -> Int #

alignment :: CTime -> Int #

peekElemOff :: Ptr CTime -> Int -> IO CTime #

pokeElemOff :: Ptr CTime -> Int -> CTime -> IO () #

peekByteOff :: Ptr b -> Int -> IO CTime #

pokeByteOff :: Ptr b -> Int -> CTime -> IO () #

peek :: Ptr CTime -> IO CTime #

poke :: Ptr CTime -> CTime -> IO () #

Storable CUSeconds 
Storable CSUSeconds 
Storable CIntPtr 
Storable CUIntPtr 
Storable CIntMax 
Storable CUIntMax 
Storable Fingerprint 
(Storable a, Integral a) => Storable (Ratio a) 

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

peekElemOff :: Ptr (Ratio a) -> Int -> IO (Ratio a) #

pokeElemOff :: Ptr (Ratio a) -> Int -> Ratio a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ratio a) #

pokeByteOff :: Ptr b -> Int -> Ratio a -> IO () #

peek :: Ptr (Ratio a) -> IO (Ratio a) #

poke :: Ptr (Ratio a) -> Ratio a -> IO () #

Storable (StablePtr a) 

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

peekElemOff :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) #

pokeElemOff :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (StablePtr a) #

pokeByteOff :: Ptr b -> Int -> StablePtr a -> IO () #

peek :: Ptr (StablePtr a) -> IO (StablePtr a) #

poke :: Ptr (StablePtr a) -> StablePtr a -> IO () #

Storable (Ptr a) 

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () #

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

Storable (FunPtr a) 

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Storable a => Storable (Complex a) 

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

peekElemOff :: Ptr (Complex a) -> Int -> IO (Complex a) #

pokeElemOff :: Ptr (Complex a) -> Int -> Complex a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Complex a) #

pokeByteOff :: Ptr b -> Int -> Complex a -> IO () #

peek :: Ptr (Complex a) -> IO (Complex a) #

poke :: Ptr (Complex a) -> Complex a -> IO () #

Storable a => Storable (Only a) 

Methods

sizeOf :: Only a -> Int #

alignment :: Only a -> Int #

peekElemOff :: Ptr (Only a) -> Int -> IO (Only a) #

pokeElemOff :: Ptr (Only a) -> Int -> Only a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Only a) #

pokeByteOff :: Ptr b -> Int -> Only a -> IO () #

peek :: Ptr (Only a) -> IO (Only a) #

poke :: Ptr (Only a) -> Only a -> IO () #

(Storable a, Arity n) => Storable (VecList n a) 

Methods

sizeOf :: VecList n a -> Int #

alignment :: VecList n a -> Int #

peekElemOff :: Ptr (VecList n a) -> Int -> IO (VecList n a) #

pokeElemOff :: Ptr (VecList n a) -> Int -> VecList n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (VecList n a) #

pokeByteOff :: Ptr b -> Int -> VecList n a -> IO () #

peek :: Ptr (VecList n a) -> IO (VecList n a) #

poke :: Ptr (VecList n a) -> VecList n a -> IO () #

Storable a => Storable (Const k a b) 

Methods

sizeOf :: Const k a b -> Int #

alignment :: Const k a b -> Int #

peekElemOff :: Ptr (Const k a b) -> Int -> IO (Const k a b) #

pokeElemOff :: Ptr (Const k a b) -> Int -> Const k a b -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Const k a b) #

pokeByteOff :: Ptr b -> Int -> Const k a b -> IO () #

peek :: Ptr (Const k a b) -> IO (Const k a b) #

poke :: Ptr (Const k a b) -> Const k a b -> IO () #

data L Source #

Linear load type index. UArrays with L load type index define linearIndex and linearWrite and leave index and write functions defined by default.

Instances

WorkIndex sh Int => PreferredWorkIndex L sh Int Source # 
(Shape sh, Storable e) => UTarget FS L sh e Source # 

Methods

write :: UArray FS L sh e -> sh -> e -> IO () Source #

linearWrite :: UArray FS L sh e -> Int -> e -> IO () Source #

(Shape sh, Storable a) => UTarget F L sh a Source # 

Methods

write :: UArray F L sh a -> sh -> a -> IO () Source #

linearWrite :: UArray F L sh a -> Int -> a -> IO () Source #

(Shape sh, NFData a) => UTarget MB L sh a Source # 

Methods

write :: UArray MB L sh a -> sh -> a -> IO () Source #

linearWrite :: UArray MB L sh a -> Int -> a -> IO () Source #

Shape sh => USource D L sh a Source # 

Methods

index :: UArray D L sh a -> sh -> IO a Source #

linearIndex :: UArray D L sh a -> Int -> IO a Source #

(Shape sh, Storable e) => USource FS L sh e Source # 

Methods

index :: UArray FS L sh e -> sh -> IO e Source #

linearIndex :: UArray FS L sh e -> Int -> IO e Source #

(Shape sh, Storable a) => USource F L sh a Source # 

Methods

index :: UArray F L sh a -> sh -> IO a Source #

linearIndex :: UArray F L sh a -> Int -> IO a Source #

(Shape sh, NFData a) => USource MB L sh a Source # 

Methods

index :: UArray MB L sh a -> sh -> IO a Source #

linearIndex :: UArray MB L sh a -> Int -> IO a Source #

(Shape sh, NFData a) => USource B L sh a Source # 

Methods

index :: UArray B L sh a -> sh -> IO a Source #

linearIndex :: UArray B L sh a -> Int -> IO a Source #

Shape sh => Regular D L sh a Source # 

Associated Types

data UArray D L sh a :: * Source #

Methods

extent :: UArray D L sh a -> sh Source #

touchArray :: UArray D L sh a -> IO () Source #

force :: UArray D L sh a -> IO () Source #

Shape sh => Regular FS L sh e Source # 

Associated Types

data UArray FS L sh e :: * Source #

Methods

extent :: UArray FS L sh e -> sh Source #

touchArray :: UArray FS L sh e -> IO () Source #

force :: UArray FS L sh e -> IO () Source #

Shape sh => Regular F L sh a Source # 

Associated Types

data UArray F L sh a :: * Source #

Methods

extent :: UArray F L sh a -> sh Source #

touchArray :: UArray F L sh a -> IO () Source #

force :: UArray F L sh a -> IO () Source #

(Shape sh, NFData a) => Regular MB L sh a Source # 

Associated Types

data UArray MB L sh a :: * Source #

Methods

extent :: UArray MB L sh a -> sh Source #

touchArray :: UArray MB L sh a -> IO () Source #

force :: UArray MB L sh a -> IO () Source #

(Shape sh, NFData a) => Regular B L sh a Source # 

Associated Types

data UArray B L sh a :: * Source #

Methods

extent :: UArray B L sh a -> sh Source #

touchArray :: UArray B L sh a -> IO () Source #

force :: UArray B L sh a -> IO () Source #

DefaultFusion D D L sh Source # 

Methods

dmap :: (USource D L sh a, USource D L sh b) => (a -> b) -> UArray D L sh a -> UArray D L sh b Source #

dmapM :: (USource D L sh a, USource D L sh b) => (a -> IO b) -> UArray D L sh a -> UArray D L sh b Source #

dzip2 :: (USource D L sh a, USource D L sh b, USource D L sh c) => (a -> b -> c) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c Source #

dzip2M :: (USource D L sh a, USource D L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c Source #

dzip3 :: (USource D L sh a, USource D L sh b, USource D L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c -> UArray D L sh d Source #

dzip3M :: (USource D L sh a, USource D L sh b, USource D L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c -> UArray D L sh d Source #

dzip :: (USource D L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray D L sh a) -> UArray D L sh b Source #

dzipM :: (USource D L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray D L sh a) -> UArray D L sh b Source #

DefaultFusion FS D L sh Source # 

Methods

dmap :: (USource FS L sh a, USource D L sh b) => (a -> b) -> UArray FS L sh a -> UArray D L sh b Source #

dmapM :: (USource FS L sh a, USource D L sh b) => (a -> IO b) -> UArray FS L sh a -> UArray D L sh b Source #

dzip2 :: (USource FS L sh a, USource FS L sh b, USource D L sh c) => (a -> b -> c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D L sh c Source #

dzip2M :: (USource FS L sh a, USource FS L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D L sh c Source #

dzip3 :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D L sh d Source #

dzip3M :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D L sh d Source #

dzip :: (USource FS L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray FS L sh a) -> UArray D L sh b Source #

dzipM :: (USource FS L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray FS L sh a) -> UArray D L sh b Source #

DefaultFusion F D L sh Source # 

Methods

dmap :: (USource F L sh a, USource D L sh b) => (a -> b) -> UArray F L sh a -> UArray D L sh b Source #

dmapM :: (USource F L sh a, USource D L sh b) => (a -> IO b) -> UArray F L sh a -> UArray D L sh b Source #

dzip2 :: (USource F L sh a, USource F L sh b, USource D L sh c) => (a -> b -> c) -> UArray F L sh a -> UArray F L sh b -> UArray D L sh c Source #

dzip2M :: (USource F L sh a, USource F L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray F L sh a -> UArray F L sh b -> UArray D L sh c Source #

dzip3 :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D L sh d Source #

dzip3M :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D L sh d Source #

dzip :: (USource F L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray F L sh a) -> UArray D L sh b Source #

dzipM :: (USource F L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray F L sh a) -> UArray D L sh b Source #

DefaultFusion MB D L sh Source # 

Methods

dmap :: (USource MB L sh a, USource D L sh b) => (a -> b) -> UArray MB L sh a -> UArray D L sh b Source #

dmapM :: (USource MB L sh a, USource D L sh b) => (a -> IO b) -> UArray MB L sh a -> UArray D L sh b Source #

dzip2 :: (USource MB L sh a, USource MB L sh b, USource D L sh c) => (a -> b -> c) -> UArray MB L sh a -> UArray MB L sh b -> UArray D L sh c Source #

dzip2M :: (USource MB L sh a, USource MB L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray MB L sh a -> UArray MB L sh b -> UArray D L sh c Source #

dzip3 :: (USource MB L sh a, USource MB L sh b, USource MB L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray MB L sh a -> UArray MB L sh b -> UArray MB L sh c -> UArray D L sh d Source #

dzip3M :: (USource MB L sh a, USource MB L sh b, USource MB L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray MB L sh a -> UArray MB L sh b -> UArray MB L sh c -> UArray D L sh d Source #

dzip :: (USource MB L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray MB L sh a) -> UArray D L sh b Source #

dzipM :: (USource MB L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray MB L sh a) -> UArray D L sh b Source #

DefaultFusion B D L sh Source # 

Methods

dmap :: (USource B L sh a, USource D L sh b) => (a -> b) -> UArray B L sh a -> UArray D L sh b Source #

dmapM :: (USource B L sh a, USource D L sh b) => (a -> IO b) -> UArray B L sh a -> UArray D L sh b Source #

dzip2 :: (USource B L sh a, USource B L sh b, USource D L sh c) => (a -> b -> c) -> UArray B L sh a -> UArray B L sh b -> UArray D L sh c Source #

dzip2M :: (USource B L sh a, USource B L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray B L sh a -> UArray B L sh b -> UArray D L sh c Source #

dzip3 :: (USource B L sh a, USource B L sh b, USource B L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray B L sh a -> UArray B L sh b -> UArray B L sh c -> UArray D L sh d Source #

dzip3M :: (USource B L sh a, USource B L sh b, USource B L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray B L sh a -> UArray B L sh b -> UArray B L sh c -> UArray D L sh d Source #

dzip :: (USource B L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray B L sh a) -> UArray D L sh b Source #

dzipM :: (USource B L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray B L sh a) -> UArray D L sh b Source #

Fusion r D L sh Source # 

Methods

fmap :: (USource r L sh a, USource D L sh b) => (a -> b) -> UArray r L sh a -> UArray D L sh b Source #

fmapM :: (USource r L sh a, USource D L sh b) => (a -> IO b) -> UArray r L sh a -> UArray D L sh b Source #

fzip2 :: (USource r L sh a, USource r L sh b, USource D L sh c) => (a -> b -> c) -> UArray r L sh a -> UArray r L sh b -> UArray D L sh c Source #

fzip2M :: (USource r L sh a, USource r L sh b, USource D L sh c) => (a -> b -> IO c) -> UArray r L sh a -> UArray r L sh b -> UArray D L sh c Source #

fzip3 :: (USource r L sh a, USource r L sh b, USource r L sh c, USource D L sh d) => (a -> b -> c -> d) -> UArray r L sh a -> UArray r L sh b -> UArray r L sh c -> UArray D L sh d Source #

fzip3M :: (USource r L sh a, USource r L sh b, USource r L sh c, USource D L sh d) => (a -> b -> c -> IO d) -> UArray r L sh a -> UArray r L sh b -> UArray r L sh c -> UArray D L sh d Source #

fzip :: (USource r L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a b -> VecList n (UArray r L sh a) -> UArray D L sh b Source #

fzipM :: (USource r L sh a, USource D L sh b, Arity n, (* ~ n) (S n0)) => Fun n a (IO b) -> VecList n (UArray r L sh a) -> UArray D L sh b Source #

(Shape sh, Storable a) => Manifest F F L sh a Source # 

Methods

new :: sh -> IO (UArray F L sh a) Source #

freeze :: UArray F L sh a -> IO (UArray F L sh a) Source #

thaw :: UArray F L sh a -> IO (UArray F L sh a) Source #

(Shape sh, NFData a) => Manifest B MB L sh a Source # 

Methods

new :: sh -> IO (UArray MB L sh a) Source #

freeze :: UArray MB L sh a -> IO (UArray B L sh a) Source #

thaw :: UArray B L sh a -> IO (UArray MB L sh a) Source #

Shape sh => DefaultIFusion D L D SH sh Source # 

Methods

imap :: (USource D L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray D L sh a -> UArray D SH sh b Source #

imapM :: (USource D L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray D L sh a -> UArray D SH sh b Source #

izip2 :: (USource D L sh a, USource D L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray D L sh a -> UArray D L sh b -> UArray D SH sh c Source #

izip2M :: (USource D L sh a, USource D L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray D L sh a -> UArray D L sh b -> UArray D SH sh c Source #

izip3 :: (USource D L sh a, USource D L sh b, USource D L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c -> UArray D SH sh d Source #

izip3M :: (USource D L sh a, USource D L sh b, USource D L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray D L sh a -> UArray D L sh b -> UArray D L sh c -> UArray D SH sh d Source #

izip :: (USource D L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray D L sh a) -> UArray D SH sh b Source #

izipM :: (USource D L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray D L sh a) -> UArray D SH sh b Source #

Shape sh => DefaultIFusion FS L D SH sh Source # 

Methods

imap :: (USource FS L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray FS L sh a -> UArray D SH sh b Source #

imapM :: (USource FS L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray FS L sh a -> UArray D SH sh b Source #

izip2 :: (USource FS L sh a, USource FS L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D SH sh c Source #

izip2M :: (USource FS L sh a, USource FS L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray FS L sh a -> UArray FS L sh b -> UArray D SH sh c Source #

izip3 :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D SH sh d Source #

izip3M :: (USource FS L sh a, USource FS L sh b, USource FS L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray FS L sh a -> UArray FS L sh b -> UArray FS L sh c -> UArray D SH sh d Source #

izip :: (USource FS L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray FS L sh a) -> UArray D SH sh b Source #

izipM :: (USource FS L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray FS L sh a) -> UArray D SH sh b Source #

Shape sh => DefaultIFusion F L D SH sh Source # 

Methods

imap :: (USource F L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray F L sh a -> UArray D SH sh b Source #

imapM :: (USource F L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray F L sh a -> UArray D SH sh b Source #

izip2 :: (USource F L sh a, USource F L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray F L sh a -> UArray F L sh b -> UArray D SH sh c Source #

izip2M :: (USource F L sh a, USource F L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray F L sh a -> UArray F L sh b -> UArray D SH sh c Source #

izip3 :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D SH sh d Source #

izip3M :: (USource F L sh a, USource F L sh b, USource F L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray F L sh a -> UArray F L sh b -> UArray F L sh c -> UArray D SH sh d Source #

izip :: (USource F L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray F L sh a) -> UArray D SH sh b Source #

izipM :: (USource F L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray F L sh a) -> UArray D SH sh b Source #

Shape sh => DefaultIFusion MB L D SH sh Source # 

Methods

imap :: (USource MB L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray MB L sh a -> UArray D SH sh b Source #

imapM :: (USource MB L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray MB L sh a -> UArray D SH sh b Source #

izip2 :: (USource MB L sh a, USource MB L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray MB L sh a -> UArray MB L sh b -> UArray D SH sh c Source #

izip2M :: (USource MB L sh a, USource MB L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray MB L sh a -> UArray MB L sh b -> UArray D SH sh c Source #

izip3 :: (USource MB L sh a, USource MB L sh b, USource MB L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray MB L sh a -> UArray MB L sh b -> UArray MB L sh c -> UArray D SH sh d Source #

izip3M :: (USource MB L sh a, USource MB L sh b, USource MB L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray MB L sh a -> UArray MB L sh b -> UArray MB L sh c -> UArray D SH sh d Source #

izip :: (USource MB L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray MB L sh a) -> UArray D SH sh b Source #

izipM :: (USource MB L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray MB L sh a) -> UArray D SH sh b Source #

Shape sh => DefaultIFusion B L D SH sh Source # 

Methods

imap :: (USource B L sh a, USource D SH sh b) => (sh -> a -> b) -> UArray B L sh a -> UArray D SH sh b Source #

imapM :: (USource B L sh a, USource D SH sh b) => (sh -> a -> IO b) -> UArray B L sh a -> UArray D SH sh b Source #

izip2 :: (USource B L sh a, USource B L sh b, USource D SH sh c) => (sh -> a -> b -> c) -> UArray B L sh a -> UArray B L sh b -> UArray D SH sh c Source #

izip2M :: (USource B L sh a, USource B L sh b, USource D SH sh c) => (sh -> a -> b -> IO c) -> UArray B L sh a -> UArray B L sh b -> UArray D SH sh c Source #

izip3 :: (USource B L sh a, USource B L sh b, USource B L sh c, USource D SH sh d) => (sh -> a -> b -> c -> d) -> UArray B L sh a -> UArray B L sh b -> UArray B L sh c -> UArray D SH sh d Source #

izip3M :: (USource B L sh a, USource B L sh b, USource B L sh c, USource D SH sh d) => (sh -> a -> b -> c -> IO d) -> UArray B L sh a -> UArray B L sh b -> UArray B L sh c -> UArray D SH sh d Source #

izip :: (USource B L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a b) -> VecList n (UArray B L sh a) -> UArray D SH sh b Source #

izipM :: (USource B L sh a, USource D SH sh b, Arity n, (* ~ n) (S n0)) => (sh -> Fun n a (IO b)) -> VecList n (UArray B L sh a) -> UArray D SH sh b Source #

(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecTarget F FS L sh v e Source # 
(Shape sh, Vector v e) => UVecSource D D L sh v e Source # 
(Shape sh, Vector v e, Storable e, Storable (v e)) => UVecSource F FS L sh v e Source # 
(Shape sh, Vector v e) => VecRegular D D L sh v e Source # 

Methods

slices :: UArray D L sh (v e) -> VecList (Dim v) (UArray D L sh e) Source #

(Shape sh, Vector v e, Storable e, Storable (v e)) => VecRegular F FS L sh v e Source # 

Methods

slices :: UArray F L sh (v e) -> VecList (Dim v) (UArray FS L sh e) Source #

Load r L tr SH sh a => RangeLoad r L tr SH sh a Source # 

Methods

rangeLoadP :: Fill sh a -> Threads -> UArray r L sh a -> UArray tr SH sh a -> sh -> sh -> IO () Source #

rangeLoadS :: Fill sh a -> UArray r L sh a -> UArray tr SH sh a -> sh -> sh -> IO () Source #

Load r SH tr L sh a => RangeLoad r SH tr L sh a Source # 

Methods

rangeLoadP :: Fill sh a -> Threads -> UArray r SH sh a -> UArray tr L sh a -> sh -> sh -> IO () Source #

rangeLoadS :: Fill sh a -> UArray r SH sh a -> UArray tr L sh a -> sh -> sh -> IO () Source #

Load r L tr L sh a => RangeLoad r L tr L sh a Source # 

Methods

rangeLoadP :: Fill sh a -> Threads -> UArray r L sh a -> UArray tr L sh a -> sh -> sh -> IO () Source #

rangeLoadS :: Fill sh a -> UArray r L sh a -> UArray tr L sh a -> sh -> sh -> IO () Source #

(USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a Source # 

Associated Types

type LoadIndex L SH sh :: * Source #

Methods

loadP :: Fill (LoadIndex L SH sh) a -> Threads -> UArray r L sh a -> UArray tr SH sh a -> IO () Source #

loadS :: Fill (LoadIndex L SH sh) a -> UArray r L sh a -> UArray tr SH sh a -> IO () Source #

(USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a Source # 

Associated Types

type LoadIndex SH L sh :: * Source #

Methods

loadP :: Fill (LoadIndex SH L sh) a -> Threads -> UArray r SH sh a -> UArray tr L sh a -> IO () Source #

loadS :: Fill (LoadIndex SH L sh) a -> UArray r SH sh a -> UArray tr L sh a -> IO () Source #

(USource r L sh a, UTarget tr L sh a, WorkIndex sh Int) => Load r L tr L sh a Source # 

Associated Types

type LoadIndex L L sh :: * Source #

Methods

loadP :: Fill (LoadIndex L L sh) a -> Threads -> UArray r L sh a -> UArray tr L sh a -> IO () Source #

loadS :: Fill (LoadIndex L L sh) a -> UArray r L sh a -> UArray tr L sh a -> IO () Source #

(VecLoad r slr L tr tslr SH sh v v2 e, RangeLoad slr L tslr SH sh e) => RangeVecLoad r slr L tr tslr SH sh v v2 e Source # 

Methods

rangeLoadSlicesP :: Fill sh e -> Threads -> UArray r L sh (v e) -> UArray tr SH sh (v2 e) -> sh -> sh -> IO () Source #

rangeLoadSlicesS :: Fill sh e -> UArray r L sh (v e) -> UArray tr SH sh (v2 e) -> sh -> sh -> IO () Source #

(VecLoad r slr SH tr tslr L sh v v2 e, RangeLoad slr SH tslr L sh e) => RangeVecLoad r slr SH tr tslr L sh v v2 e Source # 

Methods

rangeLoadSlicesP :: Fill sh e -> Threads -> UArray r SH sh (v e) -> UArray tr L sh (v2 e) -> sh -> sh -> IO () Source #

rangeLoadSlicesS :: Fill sh e -> UArray r SH sh (v e) -> UArray tr L sh (v2 e) -> sh -> sh -> IO () Source #

(VecLoad r slr L tr tslr L sh v v2 e, RangeLoad slr L tslr L sh e) => RangeVecLoad r slr L tr tslr L sh v v2 e Source # 

Methods

rangeLoadSlicesP :: Fill sh e -> Threads -> UArray r L sh (v e) -> UArray tr L sh (v2 e) -> sh -> sh -> IO () Source #

rangeLoadSlicesS :: Fill sh e -> UArray r L sh (v e) -> UArray tr L sh (v2 e) -> sh -> sh -> IO () Source #

(UVecSource r slr L sh v e, UVecTarget tr tslr SH sh v2 e, Load slr L tslr SH sh e, (~) * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr SH sh v v2 e Source # 

Methods

loadSlicesP :: Fill (LoadIndex L SH sh) e -> Threads -> UArray r L sh (v e) -> UArray tr SH sh (v2 e) -> IO () Source #

loadSlicesS :: Fill (LoadIndex L SH sh) e -> UArray r L sh (v e) -> UArray tr SH sh (v2 e) -> IO () Source #

(UVecSource r slr SH sh v e, UVecTarget tr tslr L sh v2 e, Load slr SH tslr L sh e, (~) * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr L sh v v2 e Source # 

Methods

loadSlicesP :: Fill (LoadIndex SH L sh) e -> Threads -> UArray r SH sh (v e) -> UArray tr L sh (v2 e) -> IO () Source #

loadSlicesS :: Fill (LoadIndex SH L sh) e -> UArray r SH sh (v e) -> UArray tr L sh (v2 e) -> IO () Source #

(UVecSource r slr L sh v e, UVecTarget tr tslr L sh v2 e, Load slr L tslr L sh e, (~) * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr L sh v v2 e Source # 

Methods

loadSlicesP :: Fill (LoadIndex L L sh) e -> Threads -> UArray r L sh (v e) -> UArray tr L sh (v2 e) -> IO () Source #

loadSlicesS :: Fill (LoadIndex L L sh) e -> UArray r L sh (v e) -> UArray tr L sh (v2 e) -> IO () Source #

(Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e Source # 
(Shape sh, Vector v e, NFData e) => UVecSource (SE MB) MB L sh v e Source # 
(Shape sh, Vector v e, NFData e) => UVecSource (SE B) B L sh v e Source # 
Shape sh => NFData (UArray D L sh a) # 

Methods

rnf :: UArray D L sh a -> () #

Shape sh => NFData (UArray FS L sh e) # 

Methods

rnf :: UArray FS L sh e -> () #

Shape sh => NFData (UArray F L sh a) # 

Methods

rnf :: UArray F L sh a -> () #

(Shape sh, NFData a) => NFData (UArray MB L sh a) # 

Methods

rnf :: UArray MB L sh a -> () #

(Shape sh, NFData a) => NFData (UArray B L sh a) # 

Methods

rnf :: UArray B L sh a -> () #

data UArray D L Source # 
data UArray D L = LinearDelayed !sh (IO ()) (IO ()) (Int -> IO a)
data UArray FS L Source # 
data UArray FS L = ForeignSlice !sh !Int !(ForeignPtr e) !(Ptr e)
data UArray F L Source # 
data UArray F L = ForeignArray !sh !(ForeignPtr a) !(Ptr a)
data UArray MB L Source # 
data UArray B L Source # 
data UArray B L = Boxed !sh !(Array a)
type LoadIndex SH L sh Source # 
type LoadIndex SH L sh = sh
type LoadIndex L SH sh Source # 
type LoadIndex L SH sh = sh
type LoadIndex L L sh Source # 
type LoadIndex L L sh = Int

newEmpty :: (Shape sh, Storable a, Integral a) => sh -> IO (UArray F L sh a) Source #

O(1) allocates zero-initialized foreign array.

Needed because common new function allocates array with garbage.

toForeignPtr :: Shape sh => UArray F L sh a -> ForeignPtr a Source #

O(1) Returns pointer to memory block used by the given foreign array.

May be useful to reuse memory if you don't longer need the given array in the program:

brandNewData <-
   unsafeFromForeignPtr ext (castForeignPtr (toForeignPtr arr))

unsafeFromForeignPtr :: Shape sh => sh -> ForeignPtr a -> IO (UArray F L sh a) Source #

O(1) Wraps foreign ptr into foreign array.

The function is unsafe because it simply don't (and can't) check anything about correctness of produced array.