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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Generic.Target

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 l a Source

Mutable buffer for some array representation.

Methods

unsafeNewBuffer :: l -> IO (Buffer l a) Source

Allocate a new mutable buffer for the given layout.

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

unsafeReadBuffer :: Buffer l a -> Int -> IO a Source

Read an element from the mutable buffer.

UNSAFE: The index bounds are not checked.

unsafeWriteBuffer :: Buffer l a -> Int -> a -> IO () Source

Write an element into the mutable buffer.

UNSAFE: The index bounds are not checked.

unsafeGrowBuffer :: Buffer l a -> Int -> IO (Buffer 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 :: Int -> Int -> Buffer l a -> IO (Buffer 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 :: Buffer l a -> IO (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 :: Array l a -> IO (Buffer l a) Source

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

UNSAFE: The Array is no longer safe to use.

touchBuffer :: Buffer l a -> IO () Source

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

bufferLayout :: Buffer 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.

Target A Char 
Target A Double 
Target A Float 
Target A Int 
Target A Int8 
Target A Int16 
Target A Int32 
Target A Int64 
Target A Word8 
Target A Date32 
Target A [a] 
(Bulk l a, Target l a, (~) * (Index l) Int) => Target N (Array l a) 
(Target A a, Target A b) => Target A (a, b) 
(Target A a, Target A b) => Target A ((:*:) a b) 
(Bulk l a, Target l a, (~) * (Index l) Int) => Target A (Array l a) 
(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.

fromList :: TargetI l a => Name l -> [a] -> Array l a Source

O(length src). Construct a linear array from a list of elements.

fromListInto :: Target l a => l -> [a] -> Maybe (Array l a) Source

O(length src). Construct an array from a list of elements, and give it the provided layout.

The length of the provided shape must match the length of the list, else Nothing.