repa-array-4.0.0.2: Bulk array representations and operators.

Safe HaskellNone
LanguageHaskell98

Data.Repa.Eval.Array

Contents

Synopsis

Array Targets

class Layout l => Target l a where Source

Class of manifest array representations that can be constructed in a random-access manner.

Associated Types

data Buffer s l a Source

Mutable buffer for some array representation.

Methods

unsafeNewBuffer :: PrimMonad m => l -> m (Buffer (PrimState m) l a) Source

Allocate a new mutable buffer for the given layout.

UNSAFE: The integer must be positive, but this is not checked.

unsafeReadBuffer :: PrimMonad m => Buffer (PrimState m) l a -> Int -> m a Source

Read an element from the mutable buffer.

UNSAFE: The index bounds are not checked.

unsafeWriteBuffer :: PrimMonad m => Buffer (PrimState m) l a -> Int -> a -> m () Source

Write an element into the mutable buffer.

UNSAFE: The index bounds are not checked.

unsafeGrowBuffer :: PrimMonad m => Buffer (PrimState m) l a -> Int -> m (Buffer (PrimState m) l a) Source

O(n). Copy the contents of a buffer that is larger by the given number of elements.

UNSAFE: The integer must be positive, but this is not checked.

unsafeSliceBuffer :: PrimMonad m => Int -> Int -> Buffer (PrimState m) l a -> m (Buffer (PrimState m) l a) Source

O(1). Yield a slice of the buffer without copying.

UNSAFE: The given starting position and length must be within the bounds of the of the source buffer, but this is not checked.

unsafeFreezeBuffer :: PrimMonad m => Buffer (PrimState m) l a -> m (Array l a) Source

O(1). Freeze a mutable buffer into an immutable Repa array.

UNSAFE: If the buffer is mutated further then the result of reading from the returned array will be non-deterministic.

unsafeThawBuffer :: PrimMonad m => Array l a -> m (Buffer (PrimState m) l a) Source

O(1). Thaw an Array into a mutable buffer.

UNSAFE: The Array is no longer safe to use.

touchBuffer :: PrimMonad m => Buffer (PrimState m) l a -> m () Source

Ensure the array is still live at this point. Sometimes needed when the mutable buffer is a ForeignPtr with a finalizer.

bufferLayout :: Buffer s l a -> l Source

O(1). Get the layout from a Buffer.

Instances

Target B a

Boxed buffers.

Storable a => Target F a

Foreign buffers

Unbox a => Target U a

Unboxed buffers.

(Layout l, (~) * (Index r) Int, Target r a) => Target (E r l) a

Dense buffers.

(Target l1 a, Target l2 b, (~) * (Index l1) (Index l2)) => Target (T2 l1 l2) (a, b)

Tupled buffers.

type TargetI l a = (Target l a, Index l ~ Int) Source

Constraint synonym that requires an integer index space.

Array Loading

class (Bulk l1 a, Target l2 a) => Load l1 l2 a where Source

Compute all elements defined by a delayed array and write them to a manifest target representation.

The instances of this class require that the source array has a delayed representation. If you want to use a pre-existing manifest array as the source then delay it first.

Methods

loadS :: Array l1 a -> IOBuffer l2 a -> IO () Source

Fill an entire array sequentially.

loadP :: Gang -> Array l1 a -> IOBuffer l2 a -> IO () Source

Fill an entire array in parallel.

Instances

(Layout l1, Target l2 a) => Load (D l1) l2 a 
(Layout lSrc1, Layout lSrc2, Target lDst a, (~) * (Index lSrc1) (Index lSrc2)) => Load (D2 lSrc1 lSrc2) lDst a 

computeS :: (Load lSrc lDst a, Index lSrc ~ Index lDst) => Name lDst -> Array lSrc a -> Array lDst a Source

Sequential computation of delayed array elements.

Elements of the source array are computed sequentially and written to a new array of the specified layout.

computeIntoS :: Load lSrc lDst a => lDst -> Array lSrc a -> Maybe (Array lDst a) Source

Like computeS but use the provided desination layout.

The size of the destination layout must match the size of the source array, else Nothing.