repa-3.1.3.1: High performance, regular, shape polymorphic parallel arrays.

Safe HaskellSafe-Infered

Data.Array.Repa.Eval

Contents

Description

Low level interface to parallel array filling operators.

Synopsis

Element types

class Elt a whereSource

Element types that can be used with the blockwise filling functions.

This class is mainly used to define the touch method. This is used internally in the imeplementation of Repa to prevent let-binding from being floated inappropriately by the GHC simplifier. Doing a seq sometimes isn't enough, because the GHC simplifier can erase these, and still move around the bindings.

Methods

touch :: a -> IO ()Source

Place a demand on a value at a particular point in an IO computation.

zero :: aSource

Generic zero value, helpful for debugging.

one :: aSource

Generic one value, helpful for debugging.

Instances

Elt Bool 
Elt Double 
Elt Float 
Elt Int 
Elt Int8 
Elt Int16 
Elt Int32 
Elt Int64 
Elt Word 
Elt Word8 
Elt Word16 
Elt Word32 
Elt Word64 
(Elt a, Elt b) => Elt (a, b) 
(Elt a, Elt b, Elt c) => Elt (a, b, c) 
(Elt a, Elt b, Elt c, Elt d) => Elt (a, b, c, d) 
(Elt a, Elt b, Elt c, Elt d, Elt e) => Elt (a, b, c, d, e) 
(Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Elt (a, b, c, d, e, f) 

Parallel array filling

class Fillable r e whereSource

Class of manifest array representations that can be filled in parallel and then frozen into immutable Repa arrays.

Associated Types

data MArr r e Source

Mutable version of the representation.

Methods

newMArr :: Int -> IO (MArr r e)Source

Allocate a new mutable array of the given size.

unsafeWriteMArr :: MArr r e -> Int -> e -> IO ()Source

Write an element into the mutable array.

unsafeFreezeMArr :: sh -> MArr r e -> IO (Array r sh e)Source

Freeze the mutable array into an immutable Repa array.

deepSeqMArr :: MArr r e -> a -> aSource

Ensure the strucure of a mutable array is fully evaluated.

touchMArr :: MArr r e -> IO ()Source

Ensure the array is still live at this point. Needed when the mutable array is a ForeignPtr with a finalizer.

Instances

Storable e => Fillable F e

Filling of foreign buffers.

Unbox e => Fillable U e

Filling of unboxed vector arrays.

Fillable V e

Filling of boxed vector arrays.

class (Shape sh, Repr r1 e, Fillable r2 e) => Fill r1 r2 sh e whereSource

Compute all elements defined by an array and write them to a fillable representation.

Note that instances require that the source array to have a delayed representation such as D or C. If you want to use a pre-existing manifest array as the source then delay it first.

Methods

fillS :: Array r1 sh e -> MArr r2 e -> IO ()Source

Fill an entire array sequentially.

fillP :: Array r1 sh e -> MArr r2 e -> IO ()Source

Fill an entire array in parallel.

Instances

(Shape sh, Fillable r2 e, Num e) => Fill X r2 sh e 
(Fillable r2 e, Shape sh) => Fill D r2 sh e

Compute all elements in an array.

(Fillable r2 e, Elt e) => Fill C r2 DIM2 e

Compute all elements in an rank-2 array.

(Shape sh, Fill r1 r2 sh e) => Fill (S r1) r2 sh e 
(FillRange r1 r3 sh e, Fill r2 r3 sh e, Fillable r3 e) => Fill (P r1 r2) r3 sh e 

class (Shape sh, Repr r1 e, Fillable r2 e) => FillRange r1 r2 sh e whereSource

Compute a range of elements defined by an array and write them to a fillable representation.

Methods

fillRangeS :: Array r1 sh e -> MArr r2 e -> sh -> sh -> IO ()Source

Fill a range of an array sequentially.

fillRangeP :: Array r1 sh e -> MArr r2 e -> sh -> sh -> IO ()Source

Fill a range of an array in parallel.

Instances

(Fillable r2 e, Elt e) => FillRange D r2 DIM2 e

Compute a range of elements in a rank-2 array.

(Fillable r2 e, Elt e) => FillRange C r2 DIM2 e

Compute a range of elements in a rank-2 array.

(Shape sh, FillRange r1 r2 sh e) => FillRange (S r1) r2 sh e 

fromList :: (Shape sh, Fillable r e) => sh -> [e] -> Array r sh eSource

O(n). Construct a manifest array from a list.

Converting between representations

computeS :: Fill r1 r2 sh e => Array r1 sh e -> Array r2 sh eSource

Sequential computation of array elements.

computeP :: (Shape sh, Fill r1 r2 sh e, Repr r2 e, Monad m) => Array r1 sh e -> m (Array r2 sh e)Source

Parallel computation of array elements.

  • The source array must have a delayed representation like D, C or P, and the result a manifest representation like U or F.
  • If you want to copy data between manifest representations then use copyP instead.
  • If you want to convert a manifest array back to a delayed representation then use delay instead.

suspendedComputeP :: Fill r1 r2 sh e => Array r1 sh e -> Array r2 sh eSource

Suspended parallel computation of array elements.

This version creates a thunk that will evaluate the array on demand. If you force it when another parallel computation is already running then you will get a runtime warning and evaluation will be sequential. Use deepSeqArray and now to ensure that each array is evaluated before proceeding to the next one.

If unsure then just use the monadic version computeP. This one ensures that each array is fully evaluated before continuing.

copyS :: (Repr r1 e, Fill D r2 sh e) => Array r1 sh e -> Array r2 sh eSource

Sequential copying of arrays.

copyP :: (Shape sh, Fill D r2 sh e, Repr r1 e, Repr r2 e, Monad m) => Array r1 sh e -> m (Array r2 sh e)Source

Parallel copying of arrays.

  • This is a wrapper that delays an array before calling computeP.
  • You can use it to copy manifest arrays between representations.

suspendedCopyP :: (Repr r1 e, Fill D r2 sh e) => Array r1 sh e -> Array r2 sh eSource

Suspended parallel copy of array elements.

now :: (Shape sh, Repr r e, Monad m) => Array r sh e -> m (Array r sh e)Source

Monadic version of deepSeqArray.

Forces an suspended array computation to be completed at this point in a monadic computation.

 do  let arr2 = suspendedComputeP arr1
     ...
     arr3 <- now $ arr2
     ...

Chunked filling

fillChunkedSSource

Arguments

:: Int

Number of elements.

-> (Int -> a -> IO ())

Update function to write into result buffer.

-> (Int -> a)

Fn to get the value at a given index.

-> IO () 

Fill something sequentially.

  • The array is filled linearly from start to finish.

fillChunkedPSource

Arguments

:: Int

Number of elements.

-> (Int -> a -> IO ())

Update function to write into result buffer.

-> (Int -> a)

Fn to get the value at a given index.

-> IO () 

Fill something in parallel.

  • The array is split into linear chunks and each thread fills one chunk.

fillChunkedIOPSource

Arguments

:: Int

Number of elements.

-> (Int -> a -> IO ())

Update fn to write into result buffer.

-> (Int -> IO (Int -> IO a))

Create a fn to get the value at a given index. The first Int is the thread number, so you can do some per-thread initialisation.

-> IO () 

Fill something in parallel, using a separate IO action for each thread.

Blockwise filling

fillBlock2PSource

Arguments

:: Elt a 
=> (Int -> a -> IO ())

Update function to write into result buffer.

-> (DIM2 -> a)

Function to evaluate the element at an index.

-> Int#

Width of the whole array.

-> Int#

x0 lower left corner of block to fill

-> Int#

y0

-> Int#

w0 width of block to fill.

-> Int#

h0 height of block to fill.

-> IO () 

Fill a block in a rank-2 array in parallel.

  • Blockwise filling can be more cache-efficient than linear filling for rank-2 arrays.
  • Coordinates given are of the filled edges of the block.
  • We divide the block into columns, and give one column to each thread.
  • Each column is filled in row major order from top to bottom.

fillBlock2SSource

Arguments

:: Elt a 
=> (Int -> a -> IO ())

Update function to write into result buffer.

-> (DIM2 -> a)

Function to evaluate the element at an index.

-> Int#

Width of the whole array.

-> Int#

x0 lower left corner of block to fill

-> Int#

y0

-> Int#

w0 width of block to fill

-> Int#

h0 height of block to filll

-> IO () 

Fill a block in a rank-2 array sequentially.

  • Blockwise filling can be more cache-efficient than linear filling for rank-2 arrays.
  • Coordinates given are of the filled edges of the block.
  • The block is filled in row major order from top to bottom.

Cursored blockwise filling

fillCursoredBlock2SSource

Arguments

:: Elt a 
=> (Int -> a -> IO ())

Update function to write into result buffer.

-> (DIM2 -> cursor)

Make a cursor to a particular element.

-> (DIM2 -> cursor -> cursor)

Shift the cursor by an offset.

-> (cursor -> a)

Function to evaluate an element at the given index.

-> Int#

Width of the whole array.

-> Int#

x0 lower left corner of block to fill.

-> Int#

y0

-> Int#

w0 width of block to fill

-> Int#

h0 height of block to fill

-> IO () 

Fill a block in a rank-2 array, sequentially.

  • Blockwise filling can be more cache-efficient than linear filling for rank-2 arrays.
  • Using cursor functions can help to expose inter-element indexing computations to the GHC and LLVM optimisers.
  • Coordinates given are of the filled edges of the block.
  • The block is filled in row major order from top to bottom.

fillCursoredBlock2PSource

Arguments

:: Elt a 
=> (Int -> a -> IO ())

Update function to write into result buffer.

-> (DIM2 -> cursor)

Make a cursor to a particular element.

-> (DIM2 -> cursor -> cursor)

Shift the cursor by an offset.

-> (cursor -> a)

Function to evaluate the element at an index.

-> Int#

Width of the whole array.

-> Int#

x0 lower left corner of block to fill

-> Int#

y0

-> Int#

w0 width of block to fill

-> Int#

h0 height of block to fill

-> IO () 

Fill a block in a rank-2 array in parallel.

  • Blockwise filling can be more cache-efficient than linear filling for rank-2 arrays.
  • Using cursor functions can help to expose inter-element indexing computations to the GHC and LLVM optimisers.
  • Coordinates given are of the filled edges of the block.
  • We divide the block into columns, and give one column to each thread.
  • Each column is filled in row major order from top to bottom.

Chunked selection

selectChunkedSSource

Arguments

:: Shape sh 
=> (sh -> a -> IO ())

Update function to write into result.

-> (sh -> Bool)

See if this predicate matches.

-> (sh -> a)

.. and apply fn to the matching index

-> sh

Extent of indices to apply to predicate.

-> IO Int

Number of elements written to destination array.

Select indices matching a predicate.

  • This primitive can be useful for writing filtering functions.

selectChunkedPSource

Arguments

:: forall a . Unbox a 
=> (Int -> Bool)

See if this predicate matches.

-> (Int -> a) 
-> Int 
-> IO [IOVector a] 

Select indices matching a predicate, in parallel.

  • This primitive can be useful for writing filtering functions.
  • The array is split into linear chunks, with one chunk being given to each thread.
  • The number of elements in the result array depends on how many threads you're running the program with.