Copyright | [2010..2012] Sean Seefried [2010..2016] Trevor L. McDonell |
---|---|
License | BSD3 |
Maintainer | Trevor L. McDonell <tmcdonell@cse.unsw.edu.au> |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell98 |
This module provides efficient conversion routines between different array types and Accelerate arrays.
- data A
- class (Shape r, Shape a) => Shapes r a | a -> r, r -> a
- fromRepa :: (Shapes sh sh', Elt e) => Array A sh e -> Array sh' e
- toRepa :: Shapes sh sh' => Array sh' e -> Array A sh e
- computeAccS :: (Load r sh e, Elt e) => Array r sh e -> Array A sh e
- computeAccP :: (Load r sh e, Elt e, Monad m) => Array r sh e -> m (Array A sh e)
- type family Vectors e
- toVectors :: (Shape sh, Elt e) => Array sh e -> Vectors (EltRepr e)
- fromVectors :: (Shape sh, Elt e) => sh -> Vectors (EltRepr e) -> Array sh e
- fromIArray :: (IxShapeRepr (EltRepr ix) ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix, Elt e) => a ix e -> Array sh e
- toIArray :: (IxShapeRepr (EltRepr ix) ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix) => Array sh e -> a ix e
- type RGBA32 = Word32
- readImageFromBMP :: FilePath -> IO (Either Error (Array DIM2 RGBA32))
- writeImageToBMP :: FilePath -> Array DIM2 RGBA32 -> IO ()
- type family ByteStrings e
- fromByteString :: (Shape sh, Elt e) => sh -> ByteStrings (EltRepr e) -> IO (Array sh e)
- toByteString :: (Shape sh, Elt e) => Array sh e -> IO (ByteStrings (EltRepr e))
- type family BlockPtrs e
- fromPtr :: (Shape sh, Elt e) => sh -> BlockPtrs (EltRepr e) -> IO (Array sh e)
- toPtr :: (Shape sh, Elt e) => Array sh e -> BlockPtrs (EltRepr e) -> IO ()
- type BlockCopyFun e = Ptr e -> Int -> IO ()
- type family BlockCopyFuns e
- fromArray :: (Shape sh, Elt e) => Array sh e -> BlockCopyFuns (EltRepr e) -> IO ()
- toArray :: (Shape sh, Elt e) => sh -> BlockCopyFuns (EltRepr e) -> IO (Array sh e)
Array libraries
Data.Array.Repa
This provides an efficient non-copying Repa manifest array representation that can be passed directly to Accelerate.
The standard rules for dealing with manifest Repa arrays apply:
The representation tag for manifest arrays based on Data.Array.Accelerate.
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 further computation.
class (Shape r, Shape a) => Shapes r a | a -> r, r -> a Source #
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.
toR, toA
fromRepa :: (Shapes sh sh', Elt e) => Array A sh e -> Array sh' e Source #
O(1). Unpack to an Accelerate array.
computeAccS :: (Load r sh e, Elt e) => Array r sh e -> Array A sh e Source #
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
Data.Vector.Storable
This provides an efficient non-copying conversion between storable vectors and Accelerate arrays.
type family Vectors e Source #
A family of types that represents a collection of storable Vector
s. The
structure of the collection depends on the element type e
.
For example:
- if
e :: Int
, thenVectors (EltRepr e) :: ((), Vector Int)
- if
e :: (Double, Float)
, thenVectors (EltRepr e) :: (((), Vector Double), Vector Float)
type Vectors Bool Source # | |
type Vectors Char Source # | |
type Vectors Double Source # | |
type Vectors Float Source # | |
type Vectors Int Source # | |
type Vectors Int8 Source # | |
type Vectors Int16 Source # | |
type Vectors Int32 Source # | |
type Vectors Int64 Source # | |
type Vectors Word Source # | |
type Vectors Word8 Source # | |
type Vectors Word16 Source # | |
type Vectors Word32 Source # | |
type Vectors Word64 Source # | |
type Vectors () Source # | |
type Vectors CDouble Source # | |
type Vectors CFloat Source # | |
type Vectors CULLong Source # | |
type Vectors CLLong Source # | |
type Vectors CULong Source # | |
type Vectors CLong Source # | |
type Vectors CUInt Source # | |
type Vectors CInt Source # | |
type Vectors CUShort Source # | |
type Vectors CShort Source # | |
type Vectors CUChar Source # | |
type Vectors CSChar Source # | |
type Vectors CChar Source # | |
type Vectors (a, b) Source # | |
fromVectors :: (Shape sh, Elt e) => sh -> Vectors (EltRepr e) -> Array sh e Source #
O(1). Treat a set of storable vectors as Accelerate arrays. The type of
elements e
in the output Accelerate array determines the structure of the
collection that will be required as the second argument. See Vectors
.
Data will be consumed from the vector in row-major order. You must make sure that each of the input vectors contains the right number of elements
IArray
fromIArray :: (IxShapeRepr (EltRepr ix) ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix, Elt e) => a ix e -> Array sh e Source #
Convert an IArray
to an accelerated array.
While the type signature mentions Accelerate internals that are not exported,
in practice satisfying the type equality is straight forward. The index type
ix
must be the unit type ()
for singleton arrays, or an Int
or tuple of
Int
's for multidimensional arrays.
toIArray :: (IxShapeRepr (EltRepr ix) ~ EltRepr sh, IArray a e, Ix ix, Shape sh, Elt ix) => Array sh e -> a ix e Source #
Convert an accelerated array to an IArray
.
Specialised file IO
Bitmap images
Reading and writing arrays as uncompressed 24 or 32-bit Windows BMP files.
readImageFromBMP :: FilePath -> IO (Either Error (Array DIM2 RGBA32)) Source #
Read RGBA components from a BMP file.
Low-level conversions
Copying conversions of low-level primitive data, stored in one-dimensional row-major blocks of contiguous memory. 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
Data.ByteString
type family ByteStrings e Source #
A family of types that represents a collection of ByteString
s. They are
the source data for function fromByteString
and the result data for
toByteString
type ByteStrings Bool Source # | |
type ByteStrings Char Source # | |
type ByteStrings Double Source # | |
type ByteStrings Float Source # | |
type ByteStrings Int Source # | |
type ByteStrings Int8 Source # | |
type ByteStrings Int16 Source # | |
type ByteStrings Int32 Source # | |
type ByteStrings Int64 Source # | |
type ByteStrings Word Source # | |
type ByteStrings Word8 Source # | |
type ByteStrings Word16 Source # | |
type ByteStrings Word32 Source # | |
type ByteStrings Word64 Source # | |
type ByteStrings () Source # | |
type ByteStrings CDouble Source # | |
type ByteStrings CFloat Source # | |
type ByteStrings CULLong Source # | |
type ByteStrings CLLong Source # | |
type ByteStrings CULong Source # | |
type ByteStrings CLong Source # | |
type ByteStrings CUInt Source # | |
type ByteStrings CInt Source # | |
type ByteStrings CUShort Source # | |
type ByteStrings CShort Source # | |
type ByteStrings CShort Source # | |
type ByteStrings CUChar Source # | |
type ByteStrings CSChar Source # | |
type ByteStrings CChar Source # | |
type ByteStrings (a, b) Source # | |
fromByteString :: (Shape sh, Elt e) => sh -> ByteStrings (EltRepr e) -> IO (Array sh e) Source #
Block copies bytes from a collection of ByteString
s to freshly allocated
Accelerate array.
The type of elements (e
) in the output Accelerate array determines the
structure of the collection of ByteString
s 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
ByteString
s.
The type of elements (e
) in the input Accelerate array determines the
structure of the collection of ByteString
s that will be output. See
ByteStrings
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)
type BlockPtrs Bool Source # | |
type BlockPtrs Char Source # | |
type BlockPtrs Double Source # | |
type BlockPtrs Float Source # | |
type BlockPtrs Int Source # | |
type BlockPtrs Int8 Source # | |
type BlockPtrs Int16 Source # | |
type BlockPtrs Int32 Source # | |
type BlockPtrs Int64 Source # | |
type BlockPtrs Word Source # | |
type BlockPtrs Word8 Source # | |
type BlockPtrs Word16 Source # | |
type BlockPtrs Word32 Source # | |
type BlockPtrs Word64 Source # | |
type BlockPtrs () Source # | |
type BlockPtrs CDouble Source # | |
type BlockPtrs CFloat Source # | |
type BlockPtrs CULLong Source # | |
type BlockPtrs CLLong Source # | |
type BlockPtrs CULong Source # | |
type BlockPtrs CLong Source # | |
type BlockPtrs CUInt Source # | |
type BlockPtrs CInt Source # | |
type BlockPtrs CUShort Source # | |
type BlockPtrs CShort Source # | |
type BlockPtrs CUChar Source # | |
type BlockPtrs CSChar Source # | |
type BlockPtrs CChar Source # | |
type BlockPtrs (a, b) Source # | |
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 functions
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 BlockCopyFun
s 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 ())
type BlockCopyFuns Bool Source # | |
type BlockCopyFuns Char Source # | |
type BlockCopyFuns Double Source # | |
type BlockCopyFuns Float Source # | |
type BlockCopyFuns Int Source # | |
type BlockCopyFuns Int8 Source # | |
type BlockCopyFuns Int16 Source # | |
type BlockCopyFuns Int32 Source # | |
type BlockCopyFuns Int64 Source # | |
type BlockCopyFuns Word Source # | |
type BlockCopyFuns Word8 Source # | |
type BlockCopyFuns Word16 Source # | |
type BlockCopyFuns Word32 Source # | |
type BlockCopyFuns Word64 Source # | |
type BlockCopyFuns () Source # | |
type BlockCopyFuns CDouble Source # | |
type BlockCopyFuns CFloat Source # | |
type BlockCopyFuns CULLong Source # | |
type BlockCopyFuns CLLong Source # | |
type BlockCopyFuns CULong Source # | |
type BlockCopyFuns CLong Source # | |
type BlockCopyFuns CUInt Source # | |
type BlockCopyFuns CInt Source # | |
type BlockCopyFuns CUShort Source # | |
type BlockCopyFuns CShort Source # | |
type BlockCopyFuns CUChar Source # | |
type BlockCopyFuns CSChar Source # | |
type BlockCopyFuns CChar Source # | |
type BlockCopyFuns (a, b) Source # | |
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.