accelerate-io-0.12.1.0: Read and write Accelerate arrays in various formats

Portabilitynon-portable (GHC extensions)
Stabilityexperimental
MaintainerManuel M T Chakravarty <chak@cse.unsw.edu.au>
Safe HaskellSafe-Infered

Data.Array.Accelerate.IO

Contents

Description

This module provides efficient conversion routines between different array types and Accelerate arrays.

The Repa interface provides an efficient non-copying instance for Repa to read and write directly into arrays that can then be passed to Accelerate. Additional copying conversions of low-level primitive arrays (i.e. one dimensional, row-major blocks of contiguous memory) are provided, however to use these you should really know what you are doing. Potential pitfalls include:

  • copying from memory your program doesn't have access to (e.g. it may be unallocated, or not enough memory is allocated)
  • memory alignment errors

Synopsis

Copy to/from (strict) ByteString`s

type family ByteStrings e Source

A family of types that represents a collection of ByteStrings. They are the source data for function fromByteString and the result data for toByteString

fromByteString :: (Shape sh, Elt e) => sh -> ByteStrings (EltRepr e) -> IO (Array sh e)Source

Block copies bytes from a collection of ByteStrings to freshly allocated Accelerate array.

The type of elements (e) in the output Accelerate array determines the structure of the collection of ByteStrings that will be required as the second argument to this function. See ByteStrings

toByteString :: (Shape sh, Elt e) => Array sh e -> IO (ByteStrings (EltRepr e))Source

Block copy from an Accelerate array to a collection of freshly allocated ByteStrings.

The type of elements (e) in the input Accelerate array determines the structure of the collection of ByteStrings that will be output. See ByteStrings

Copying to/from raw pointers

type family BlockPtrs e Source

A family of types that represents a collection of pointers that are the source/destination addresses for a block copy. The structure of the collection of pointers depends on the element type e.

e.g.

If e :: Int, then BlockPtrs (EltRepr e) :: ((), Ptr Int)

If e :: (Double, Float) then BlockPtrs (EltRepr e) :: (((), Ptr Double), Ptr Float)

fromPtr :: (Shape sh, Elt e) => sh -> BlockPtrs (EltRepr e) -> IO (Array sh e)Source

Block copy regions of memory into a freshly allocated Accelerate array. The type of elements (e) in the output Accelerate array determines the structure of the collection of pointers that will be required as the second argument to this function. See BlockPtrs

Each one of these pointers points to a block of memory that is the source of data for the Accelerate array (unlike function toArray where one passes in function which copies data to a destination address.).

toPtr :: (Shape sh, Elt e) => Array sh e -> BlockPtrs (EltRepr e) -> IO ()Source

Block copy from Accelerate array to pre-allocated regions of memory. The type of element of the input Accelerate array (e) determines the structure of the collection of pointers that will be required as the second argument to this function. See BlockPtrs

The memory associated with the pointers must have already been allocated.

Direct copying into/from an Accelerate array

type BlockCopyFun e = Ptr e -> Int -> IO ()Source

Functions of this type are passed as arguments to toArray. A function of this type should copy a number of bytes (equal to the value of the parameter of type Int) to the destination memory pointed to by Ptr e.

type family BlockCopyFuns e Source

Represents a collection of block copy functions (see BlockCopyFun). The structure of the collection of BlockCopyFuns depends on the element type e.

e.g.

If e :: Float then BlockCopyFuns (EltRepr e) :: ((), Ptr Float -> Int -> IO ())

If e :: (Double, Float) then BlockCopyFuns (EltRepr e) :: (((), Ptr Double -> Int -> IO ()), Ptr Float -> Int -> IO ())

fromArray :: (Shape sh, Elt e) => Array sh e -> BlockCopyFuns (EltRepr e) -> IO ()Source

Copy values from an Accelerate array using a collection of functions that have type BlockCopyFun. The argument of type Ptr e in each of these functions refers to the address of the source block of memory in the Accelerate Array. The destination address is implicit. e.g. the BlockCopyFun could be the result of partially application to a Ptr e pointing to the destination block.

The structure of this collection of functions depends on the elemente type e. Each function (of type BlockCopyFun) copies data to a destination address (pointed to by the argument of type Ptr ()).

Unless there is a particularly pressing reason to use this function, the fromPtr function is sufficient as it uses an efficient low-level call to libc's memcpy to perform the copy.

toArray :: (Shape sh, Elt e) => sh -> BlockCopyFuns (EltRepr e) -> IO (Array sh e)Source

Copy values to a freshly allocated Accelerate array using a collection of functions that have type BlockCopyFun. The argument of type Ptr e in each of these functions refers to the address of the destination block of memory in the Accelerate Array. The source address is implicit. e.g. the BlockCopyFun could be the result of a partial application to a Ptr e pointing to the source block.

The structure of this collection of functions depends on the elemente type e. Each function (of type BlockCopyFun) copies data to a destination address (pointed to by the argument of type Ptr ()).

Unless there is a particularly pressing reason to use this function, the fromPtr function is sufficient as it uses an efficient low-level call to libc's memcpy to perform the copy.

data A Source

An implementation based on Accelerate arrays. The Accelerate array implementation is based on type families and picks an efficient, unboxed representation for every element type. Moreover, these arrays can be handed efficiently (without copying) to Accelerate programs for, example, further parallel computation on the GPU.

Instances

Elt e => Target A e

Filling Accelerate arrays

Elt e => Source A e

Reading elements of the Accelerate array

class (Shape r, Shape a) => Shapes r a | a -> r, r -> aSource

Index conversion and equivalence statement between Repa and Accelerate array shapes. That is, a n-dimensional Repa array will produce an n-dimensional accelerate array of the same extent, and vice-versa.

Instances

Shapes Z Z 
Shapes sr sa => Shapes (:. sr Int) (:. sa Int) 

fromRepa :: (Shapes sh sh', Elt e) => Array A sh e -> Array sh' eSource

O(1). Unpack to an Accelerate array.

toRepa :: Shapes sh sh' => Array sh' e -> Array A sh eSource

O(1). Wrap an Accelerate array.

computeAccS :: (Load r sh e, Elt e) => Array r sh e -> Array A sh eSource

Sequential computation of array elements

computeAccP :: (Load r sh e, Elt e, Monad m) => Array r sh e -> m (Array A sh e)Source

Parallel computation of array elements

Vector conversions

fromVector :: (Storable a, Elt a, BlockPtrs (EltRepr a) ~ ((), Ptr a)) => Vector a -> Array DIM1 aSource

toVector :: (Storable a, Elt a, BlockPtrs (EltRepr a) ~ ((), Ptr a)) => Array DIM1 a -> Vector aSource

fromVectorIO :: (Storable a, Elt a, BlockPtrs (EltRepr a) ~ ((), Ptr a)) => Vector a -> IO (Array DIM1 a)Source

toVectorIO :: (Storable a, Elt a, BlockPtrs (EltRepr a) ~ ((), Ptr a)) => Array DIM1 a -> IO (Vector a)Source