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

Copyright[2012..2014] Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Repa.Repr.Accelerate

Description

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:

  • If you want to have Repa computeP directly into an Accelerate array, the source array must have a delayed representation.
  • If you want to copy between manifest arrays, use copyP instead.

Synopsis

Documentation

data A Source #

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.

Instances

Elt e => Target A e Source #

Filling Accelerate arrays

Associated Types

data MVec A e :: * #

Methods

newMVec :: Int -> IO (MVec A e) #

unsafeWriteMVec :: MVec A e -> Int -> e -> IO () #

unsafeFreezeMVec :: sh -> MVec A e -> IO (Array A sh e) #

deepSeqMVec :: MVec A e -> a -> a #

touchMVec :: MVec A e -> IO () #

Elt e => Source A e Source #

Reading elements of the Accelerate array

Associated Types

data Array A sh e :: * #

Methods

extent :: Shape sh => Array A sh e -> sh #

index :: Shape sh => Array A sh e -> sh -> e #

unsafeIndex :: Shape sh => Array A sh e -> sh -> e #

linearIndex :: Shape sh => Array A sh e -> Int -> e #

unsafeLinearIndex :: Shape sh => Array A sh e -> Int -> e #

deepSeqArray :: Shape sh => Array A sh e -> b -> b #

data MVec A Source # 
data MVec A = MAVec (MutableArrayData (EltRepr e))
data Array A Source # 
data Array A = AAccelerate !sh !(ArrayData (EltRepr e))

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.

Minimal complete definition

toR, toA

Instances

Shapes Z Z Source # 

Methods

toR :: Z -> Z

toA :: Z -> Z

Shapes sr sa => Shapes ((:.) sr Int) ((:.) sa Int) Source # 

Methods

toR :: (sa :. Int) -> sr :. Int

toA :: (sr :. Int) -> sa :. Int

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

O(1). Unpack to an Accelerate array.

toRepa :: Shapes sh sh' => Array sh' e -> Array A sh e Source #

O(1). Wrap 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