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

Safe HaskellNone
LanguageHaskell98

Data.Repa.Array.Generic.Target

Synopsis

Documentation

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 Source #

Boxed buffers.

Storable a => Target F a Source #

Foreign buffers

Unbox a => Target U a Source #

Unboxed buffers.

(Bulk l a, Target l a, (~) * (Index l) Int) => Target N (Array l a) Source # 

Associated Types

data Buffer N (Array l a) :: * Source #

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

Dense buffers.

Associated Types

data Buffer (E r l) a :: * Source #

Methods

unsafeNewBuffer :: E r l -> IO (Buffer (E r l) a) Source #

unsafeReadBuffer :: Buffer (E r l) a -> Int -> IO a Source #

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

unsafeGrowBuffer :: Buffer (E r l) a -> Int -> IO (Buffer (E r l) a) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (E r l) a -> IO (Buffer (E r l) a) Source #

unsafeFreezeBuffer :: Buffer (E r l) a -> IO (Array (E r l) a) Source #

unsafeThawBuffer :: Array (E r l) a -> IO (Buffer (E r l) a) Source #

touchBuffer :: Buffer (E r l) a -> IO () Source #

bufferLayout :: Buffer (E r l) a -> E r l Source #

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

Tupled buffers.

Associated Types

data Buffer (T2 l1 l2) (a, b) :: * Source #

Methods

unsafeNewBuffer :: T2 l1 l2 -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeReadBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (a, b) Source #

unsafeWriteBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> (a, b) -> IO () Source #

unsafeGrowBuffer :: Buffer (T2 l1 l2) (a, b) -> Int -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeSliceBuffer :: Int -> Int -> Buffer (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

unsafeFreezeBuffer :: Buffer (T2 l1 l2) (a, b) -> IO (Array (T2 l1 l2) (a, b)) Source #

unsafeThawBuffer :: Array (T2 l1 l2) (a, b) -> IO (Buffer (T2 l1 l2) (a, b)) Source #

touchBuffer :: Buffer (T2 l1 l2) (a, b) -> IO () Source #

bufferLayout :: Buffer (T2 l1 l2) (a, b) -> T2 l1 l2 Source #

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

Constraint synonym that requires an integer index space.

empty :: TargetI l a => Name l -> Array l a Source #

O(1). An empty array of the given layout.

singleton :: TargetI l a => Name l -> a -> Array l a Source #

O(1). Create a new empty array containing a single element.

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.

generateMaybeS :: TargetI l a => Name l -> Int -> (Int -> Maybe a) -> Maybe (Array l a) Source #

Generate an array of the given length by applying a function to every index, sequentially. If any element returns Nothing, then Nothing for the whole array.

mapMaybeS :: (BulkI lSrc a, TargetI lDst b) => Name lDst -> (a -> Maybe b) -> Array lSrc a -> Maybe (Array lDst b) Source #

Apply a function to every element of an array, if any application returns Nothing, then Nothing for the whole result.

generateEitherS :: TargetI l a => Name l -> Int -> (Int -> Either err a) -> Either err (Array l a) Source #

Generate an array of the given length by applying a function to every index, sequentially. If any element returns Left, then Left for the whole array.

mapEitherS :: (BulkI lSrc a, TargetI lDst b) => Name lDst -> (a -> Either err b) -> Array lSrc a -> Either err (Array lDst b) Source #

Apply a function to every element of an array, if any application returns Left, then Left for the whole result.