Skip to content
tmcdonell edited this page Dec 12, 2011 · 40 revisions

This section covers ways in which to build arrays for use in Accelerate.

Array types

Accelerate supports as array elements only simple atomic types, and tuples thereof. These element types can be stored efficiently in memory as consecutive memory slots without pointers. This feature is important to support backend implementations on exotic hardware, such as accelerate-cuda.

The supported array element types are members of the Elt class, including:

  • ()
  • Z (for storing multidimensional array indices)
  • Int, Int8, Int16, Int32, Int64
  • Word, Word8, Word16, Word32, Word64
  • Float
  • Double
  • Char
  • Bool
  • Tuple types up to 9-tuples, where the elements themselves are in Elt (this includes nested tuples)

Getting data in

Converting from lists

You can create Accelerate arrays in many ways, for example, from a regular Haskell list using the following function:

fromList :: (Shape sh, Elt e) => sh -> [e] -> Array sh e

This will generate a multidimensional array by consuming elements from the list and adding them to the array in row-major order --- that is, the right-most index of the Shape type will change most rapidly.

Note that we will often need to add an explicit type signature to our arrays to help the type checker along, unless this can be deduced from the surrounding context.

Prelude Data.Array.Accelerate
> fromList (Z:.10) [0..]

<interactive>:0:1:
    No instance for (Shape (Z :. head0))
      arising from a use of `fromList'
    Possible fix: add an instance declaration for (Shape (Z :. head0))
    In the expression: fromList (Z :. 10) [0 .. ]
    In an equation for `it': it = fromList (Z :. 10) [0 .. ]

Prelude Data.Array.Accelerate
> fromList (Z:.10) [0..] :: Array DIM1 Float
Array (Z :. 10) [0.0,1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]

Accelerate will often attempt to intimidate you with scary type errors, but persist and ye shall be rewarded.

We can also generate multidimensional arrays in this fashion

Prelude Data.Array.Accelerate
> fromList (Z:.2:.5) [1,1,1,1,1,2,2,2,2,2] :: Array DIM2 Int
Array (Z :. 2 :. 5) [1,1,1,1,1,2,2,2,2,2]

This creates a two-dimensional array with two rows of five elements each, the first row consisting entirely 1's and the second row of 2's.

Converting form Data.IArray

Similarly, we can convert immutable arrays directly to Accelerate arrays using the following function:

fromIArray
  :: (IArray a e,
      Ix ix,
      Shape sh,
      Elt ix,
      Elt e,
      Data.Array.Accelerate.Array.Sugar.EltRepr ix
        ~
      Data.Array.Accelerate.Array.Sugar.EltRepr sh) =>
     a ix e -> A.Array sh e

This has a scary type signature, because it mentions some Accelerate internals that we can't get our hands on. The EltRepr type equality ensures the dimensionality of the input IArray and output Accelerate array match.

In practice satisfying this type signature is quite simple; namely the index type Ix of our input array must be an Int, or a tuple of Int's for multidimensional arrays.

To convert a one-dimensional IArray:

Prelude Data.Array.Unboxed Data.Array.Accelerate
> let vec = listArray (0,9) [0..] :: UArray Int Float

Prelude Data.Array.Unboxed Data.Array.Accelerate
> vec
array (0,9) [(0,0.0),(1,1.0),(2,2.0),(3,3.0),(4,4.0),(5,5.0),(6,6.0),(7,7.0),(8,8.0),(9,9.0)]

Prelude Data.Array.Unboxed Data.Array.Accelerate
> fromIArary vec :: Vector Float
Array (Z :. 10) [0.0,1.0,2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]

Similarly, we can convert multidimensional arrays:

Prelude Data.Array.Unboxed Data.Array.Accelerate
> let mat = listArray ((0,0), (1,4)) [1,1,1,1,1,2,2,2,2,2] :: UArray (Int,Int) Int

Prelude Data.Array.Unboxed Data.Array.Accelerate
> fromIArray mat :: Array DIM2 Int
Array (Z :. 2 :. 5) [1,1,1,1,1,2,2,2,2,2]

Note that index ranges for IArray's are inclusive in the first and last index, whereas Accelerate uses an exclusive final index.

Converting from Data.Vector

Impure arrays

On the Haskell side, arrays can be created and operated on in a mutable fashion, using destructive updates as in an imperative language. Once all operations are complete, the mutable array can be frozen and the pure immutable array lifted into Accelerate.

Mutable arrays combined with freezing are quite useful for initialising arrays using data from the outside world.

For example, to fill an array we:

  • allocate an empty mutable IArray of size n
  • destructively update the cells using a generator function
  • freeze the IArray and convert to an Accelerate array

Here we initialise a mutable unboxed vector, fill it with randomly generated values, then convert the result into an Accelerate array.

{-# LANGUAGE BangPatterns, FlexibleContexts, ScopedTypeVariables #-}

import System.Random.MWC
import Data.Array.IO                            ( IOUArray )
import Data.Array.Unboxed                       ( IArray, UArray )
import Data.Array.MArray                        as M
import Data.Array.Accelerate                    as A

randoms
  :: forall e. (Variate e, Elt e, MArray IOUArray e IO, IArray UArray e)
  => GenIO
  -> Int
  -> IO (A.Array DIM1 e)
randoms gen n = do
  m     <- M.newArray_ (0,n-1)
  m'    <- fill m 0
  return $ A.fromIArray m'
  where
    fill :: IOUArray Int e -> Int -> IO (UArray Int e)
    fill !m !i
      | i < n     = do v <- uniform gen
                       M.writeArray m i v
                       fill m (i+1)
      | otherwise = M.unsafeFreeze m

Low-level conversions

TODO: using the accelerate-io package to read from pointers and ByteStrings.

Clone this wiki locally