repa-3.4.1.2: High performance, regular, shape polymorphic parallel arrays.

Safe HaskellNone
LanguageHaskell98

Data.Array.Repa.Repr.ForeignPtr

Synopsis

Documentation

data F Source #

Arrays represented as foreign buffers in the C heap.

Instances

Storable a => Source F a Source #

Read elements from a foreign buffer.

Associated Types

data Array F sh a :: * Source #

Methods

extent :: Shape sh => Array F sh a -> sh Source #

index :: Shape sh => Array F sh a -> sh -> a Source #

unsafeIndex :: Shape sh => Array F sh a -> sh -> a Source #

linearIndex :: Shape sh => Array F sh a -> Int -> a Source #

unsafeLinearIndex :: Shape sh => Array F sh a -> Int -> a Source #

deepSeqArray :: Shape sh => Array F sh a -> b -> b Source #

Storable e => Target F e Source #

Filling foreign buffers.

Associated Types

data MVec F e :: * Source #

Methods

newMVec :: Int -> IO (MVec F e) Source #

unsafeWriteMVec :: MVec F e -> Int -> e -> IO () Source #

unsafeFreezeMVec :: sh -> MVec F e -> IO (Array F sh e) Source #

deepSeqMVec :: MVec F e -> a -> a Source #

touchMVec :: MVec F e -> IO () Source #

Storable a => Structured F a b Source # 

Associated Types

type TR F :: * Source #

Methods

smap :: Shape sh => (a -> b) -> Array F sh a -> Array (TR F) sh b Source #

szipWith :: (Shape sh, Source r c) => (c -> a -> b) -> Array r sh c -> Array F sh a -> Array (TR F) sh b Source #

data Array F Source # 
data Array F = AForeignPtr !sh !Int !(ForeignPtr a)
data MVec F Source # 
data MVec F = FPVec !Int !(ForeignPtr e)
type TR F Source # 
type TR F = D

fromForeignPtr :: Shape sh => sh -> ForeignPtr e -> Array F sh e Source #

O(1). Wrap a ForeignPtr as an array.

toForeignPtr :: Array F sh e -> ForeignPtr e Source #

O(1). Unpack a ForeignPtr from an array.

computeIntoS :: (Load r1 sh e, Storable e) => ForeignPtr e -> Array r1 sh e -> IO () Source #

Compute an array sequentially and write the elements into a foreign buffer without intermediate copying. If you want to copy a pre-existing manifest array to a foreign buffer then delay it first.

computeIntoP :: (Load r1 sh e, Storable e) => ForeignPtr e -> Array r1 sh e -> IO () Source #

Compute an array in parallel and write the elements into a foreign buffer without intermediate copying. If you want to copy a pre-existing manifest array to a foreign buffer then delay it first.