| Safe Haskell | None |
|---|
Data.Yarr.Eval
Description
Loading and computing arrays
- type Threads = IO Int
- caps :: Threads
- threads :: Int -> Threads
- type Fill sh a = (sh -> IO a) -> (sh -> a -> IO ()) -> Work sh ()
- class (USource r l sh a, UTarget tr tl sh a, WorkIndex sh (LoadIndex l tl sh)) => Load r l tr tl sh a where
- class Load r l tr tl sh a => RangeLoad r l tr tl sh a where
- class (UVecSource r slr l sh v e, UVecTarget tr tslr tl sh v2 e, Load slr l tslr tl sh e, Dim v ~ Dim v2) => VecLoad r slr l tr tslr tl sh v v2 e where
- class (VecLoad r slr l tr tslr tl sh v v2 e, RangeLoad slr l tslr tl sh e) => RangeVecLoad r slr l tr tslr tl sh v v2 e where
- compute :: (USource r l sh a, Manifest tr mtr tl sh b) => (UArray r l sh a -> UArray mtr tl sh b -> IO ()) -> UArray r l sh a -> IO (UArray tr tl sh b)
- dComputeP :: (USource r l sh a, Manifest tr mtr tl sh a, Load r l mtr tl sh a) => UArray r l sh a -> IO (UArray tr tl sh a)
- dComputeS :: (USource r l sh a, Manifest tr mtr tl sh a, Load r l mtr tl sh a) => UArray r l sh a -> IO (UArray tr tl sh a)
- data L
- data SH
- entire :: (Regular r l sh a, Regular r2 l2 sh b) => UArray r l sh a -> UArray r2 l2 sh b -> sh
Aliases for common parameters
There are 2 common ways to parameterize
parallelism: a) to say "split this work between n threads"
or b) to say "split this work between maximum reasonable
number of threads", that is capabilities. Since
getNumCapabilities function is monadic, we need always pass
IO Int as thread number parameter in order not to multiply
number of functions in this module (there are already too many).
Alias to getNumCapabilities.
Arguments
| = (sh -> IO a) | Indexing function |
| -> (sh -> a -> IO ()) | Writing function |
| -> Work sh () | Curried result function -- worker |
Alias to frequently used get-write-from-to arguments combo.
To be passed as 1st parameter of all Loading functions
from Data.Yarr.Eval module.
Load classes
class (USource r l sh a, UTarget tr tl sh a, WorkIndex sh (LoadIndex l tl sh)) => Load r l tr tl sh a whereSource
This class abstracts pair of array types, which could be loaded one to another.
Parameters:
-
r- source representation. Instance ofUSourceclass. Typically one of fused representations:D,(orSED)CV. -
l- source load type -
tr- target representation. Instance ofUTargetclass. -
tl- target load type -
sh- shape of arrays -
a- array element type
Counterpart for arrays of vectors: VecLoad.
TODO: this class seems to be overengineered, normally
it should have only 3 parameters: Load l tl sh.
But Convoluted (CV) representation is
tightly connected with it's load type.
Associated Types
Used in fill parameter function.
There are two options for this type to be: sh itself or Int.
Don't confuse this type with load type indexes: r and l.
There are 2 different meanings of word "index": data type index
(haskell term) and array index (linear, shape).
Methods
Arguments
| :: Fill (LoadIndex l tl sh) a | Filling (real worker) function |
| -> Threads | Number of threads to parallelize loading on |
| -> UArray r l sh a | Source array |
| -> UArray tr tl sh a | Target array |
| -> IO () |
O(n) Entirely loads source to target in parallel.
First parameter is used to parameterize loop
unrolling to maximize performance.
Default choice is fill -- vanilla not unrolled looping.
Examples:
tarr <-new(extentarr) loadPfillcapsarr tarr loadP (dim2BlockFilln2n2touch) (threads2) arr tarr
Instances
| (USource r SH sh a, UTarget tr SH sh a) => Load r SH tr SH sh a | |
| (USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a | |
| (USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a | |
| (USource r L sh a, UTarget tr L sh a, WorkIndex sh Int) => Load r L tr L sh a | |
| (BlockShape sh, UTarget tr tl sh a) => Load CV CVL tr tl sh a |
class Load r l tr tl sh a => RangeLoad r l tr tl sh a whereSource
Class abstracts pair of arrays which could be loaded in just specified range of indices.
"Range" is a multidimensional
segment: segment for Dim1 arrays, square for Dim2 arrays and
cube for Dim3. Thus, it is specified by pair of indices:
"top-left" (minimum is zero) and "bottom-right" (maximum is
() corners.
entire arr tarr)
Methods
Arguments
| :: Fill sh a | Filling (real worker) function |
| -> Threads | Number of threads to parallelize loading on |
| -> UArray r l sh a | Source array |
| -> UArray tr tl sh a | Target array |
| -> sh | Top-left |
| -> sh | and bottom-right corners of range to load |
| -> IO () |
O(n) Loads elements from source to target in specified range in parallel.
Example:
let ext = extent convolved res <- new ext rangeLoadPfillcapsconvolved res (5, 5) (ext `minus` (5, 5))
Arguments
| :: Fill sh a | Filling (real worker) function |
| -> UArray r l sh a | Source array |
| -> UArray tr tl sh a | Target array |
| -> sh | Top-left |
| -> sh | and bottom-right corners of range to load |
| -> IO () |
O(n) Sequentially loads elements from source to target in specified range.
class (UVecSource r slr l sh v e, UVecTarget tr tslr tl sh v2 e, Load slr l tslr tl sh e, Dim v ~ Dim v2) => VecLoad r slr l tr tslr tl sh v v2 e whereSource
Class abstracts separated in time and space loading slices of one array type
to another. Result of running functions with -Slices- infix
is always identical to result of running corresponding function from
Load class. VecLoad and RangeVecLoad are just about performance.
If target representation is separate (ex. (),
using SE F)loadSlicesP may be faster than loadP because of per-thread memory
locality.
Parameters:
-
r- source representation -
slr- source slice representation -
l- source load type -
tr- target representation -
tslr- target slice representation -
tl- target load type -
sh- shape of arrays -
v- source vector type -
v2- target vector type -
e- vector element type, common for source and target arrays
Methods
Arguments
| :: Fill (LoadIndex l tl sh) e | Fill function to work on slices |
| -> Threads | Number of threads to parallelize loading on |
| -> UArray r l sh (v e) | Source array of vectors |
| -> UArray tr tl sh (v2 e) | Target array of vectors |
| -> IO () |
O(n) Entirely, slice-wise loads vectors from source to target in parallel.
Example:
-- blurred and delayedBlurred are arrays of color components. loadSlicesPfillcapsdelayedBlurred blurred
Arguments
| :: Fill (LoadIndex l tl sh) e | Fill function to work on slices |
| -> UArray r l sh (v e) | Source array of vectors |
| -> UArray tr tl sh (v2 e) | Target array of vectors |
| -> IO () |
O(n) Sequentially loads vectors from source to target, slice by slice.
Instances
| (UVecSource r slr SH sh v e, UVecTarget tr tslr SH sh v2 e, Load slr SH tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr SH sh v v2 e | |
| (UVecSource r slr L sh v e, UVecTarget tr tslr SH sh v2 e, Load slr L tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr SH sh v v2 e | |
| (UVecSource r slr SH sh v e, UVecTarget tr tslr L sh v2 e, Load slr SH tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr L sh v v2 e | |
| (UVecSource r slr L sh v e, UVecTarget tr tslr L sh v2 e, Load slr L tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr L sh v v2 e | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => VecLoad (SE CV) CV CVL tr tslr tl sh v v2 e |
class (VecLoad r slr l tr tslr tl sh v v2 e, RangeLoad slr l tslr tl sh e) => RangeVecLoad r slr l tr tslr tl sh v v2 e whereSource
This class extends VecLoad just like RangeLoad extends Load.
It abstracts slice-wise loading from one array type to
another in specified range.
Methods
Arguments
| :: Fill sh e | Fill function to work on slices |
| -> Threads | Number of threads to parallelize loading on |
| -> UArray r l sh (v e) | Source array of vectors |
| -> UArray tr tl sh (v2 e) | Target array of vectors |
| -> sh | Top-left |
| -> sh | and bottom-right corners of range to load |
| -> IO () |
O(n) Loads vectors from source to target in specified range, slice-wise, in parallel.
Arguments
| :: Fill sh e | Fill function to work on slices |
| -> UArray r l sh (v e) | Source array of vectors |
| -> UArray tr tl sh (v2 e) | Target array of vectors |
| -> sh | Top-left |
| -> sh | and bottom-right corners of range to load |
| -> IO () |
O(n) Sequentially loads vector elements from source to target in specified range, slice by slice.
Instances
| (VecLoad r slr SH tr tslr SH sh v v2 e, RangeLoad slr SH tslr SH sh e) => RangeVecLoad r slr SH tr tslr SH sh v v2 e | |
| (VecLoad r slr L tr tslr SH sh v v2 e, RangeLoad slr L tslr SH sh e) => RangeVecLoad r slr L tr tslr SH sh v v2 e | |
| (VecLoad r slr SH tr tslr L sh v v2 e, RangeLoad slr SH tslr L sh e) => RangeVecLoad r slr SH tr tslr L sh v v2 e | |
| (VecLoad r slr L tr tslr L sh v v2 e, RangeLoad slr L tslr L sh e) => RangeVecLoad r slr L tr tslr L sh v v2 e | |
| (BlockShape sh, Vector v e, UVecTarget tr tslr tl sh v2 e, ~ * (Dim v) (Dim v2), InlinableArity (Dim v)) => RangeVecLoad (SE CV) CV CVL tr tslr tl sh v v2 e |
Compute functions
dComputeP :: (USource r l sh a, Manifest tr mtr tl sh a, Load r l mtr tl sh a) => UArray r l sh a -> IO (UArray tr tl sh a)Source
dComputeS :: (USource r l sh a, Manifest tr mtr tl sh a, Load r l mtr tl sh a) => UArray r l sh a -> IO (UArray tr tl sh a)Source
Common load types
Linear load type index. UArrays with L load type index
define linearIndex and linearWrite and leave index and write
functions defined by default.
Instances
| WorkIndex sh Int => PreferredWorkIndex L sh Int | |
| (Shape sh, Storable e) => UTarget FS L sh e | |
| (Shape sh, Storable a) => UTarget F L sh a | |
| (Shape sh, NFData a) => UTarget MB L sh a | |
| Shape sh => USource D L sh a | |
| (Shape sh, Storable e) => USource FS L sh e | |
| (Shape sh, Storable a) => USource F L sh a | |
| (Shape sh, NFData a) => USource MB L sh a | |
| (Shape sh, NFData a) => USource B L sh a | |
| Shape sh => Regular D L sh a | |
| Shape sh => Regular FS L sh e | |
| Shape sh => Regular F L sh a | |
| (Shape sh, NFData a) => Regular MB L sh a | |
| (Shape sh, NFData a) => Regular B L sh a | |
| DefaultFusion D D L sh | |
| DefaultFusion FS D L sh | |
| DefaultFusion F D L sh | |
| DefaultFusion MB D L sh | |
| DefaultFusion B D L sh | |
| Fusion r D L sh | |
| (Shape sh, Storable a) => Manifest F F L sh a | |
| (Shape sh, NFData a) => Manifest B MB L sh a | |
| Shape sh => DefaultIFusion D L D SH sh | |
| Shape sh => DefaultIFusion FS L D SH sh | |
| Shape sh => DefaultIFusion F L D SH sh | |
| Shape sh => DefaultIFusion MB L D SH sh | |
| Shape sh => DefaultIFusion B L D SH sh | |
| (Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e | |
| (Shape sh, Vector v e) => UVecSource D D L sh v e | |
| (Shape sh, Vector v e, Storable e) => UVecSource F FS L sh v e | |
| (Shape sh, Vector v e) => VecRegular D D L sh v e | |
| (Shape sh, Vector v e, Storable e) => VecRegular F FS L sh v e | |
| Load r L tr SH sh a => RangeLoad r L tr SH sh a | |
| Load r SH tr L sh a => RangeLoad r SH tr L sh a | |
| Load r L tr L sh a => RangeLoad r L tr L sh a | |
| (USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a | |
| (USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a | |
| (USource r L sh a, UTarget tr L sh a, WorkIndex sh Int) => Load r L tr L sh a | |
| (VecLoad r slr L tr tslr SH sh v v2 e, RangeLoad slr L tslr SH sh e) => RangeVecLoad r slr L tr tslr SH sh v v2 e | |
| (VecLoad r slr SH tr tslr L sh v v2 e, RangeLoad slr SH tslr L sh e) => RangeVecLoad r slr SH tr tslr L sh v v2 e | |
| (VecLoad r slr L tr tslr L sh v v2 e, RangeLoad slr L tslr L sh e) => RangeVecLoad r slr L tr tslr L sh v v2 e | |
| (UVecSource r slr L sh v e, UVecTarget tr tslr SH sh v2 e, Load slr L tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr SH sh v v2 e | |
| (UVecSource r slr SH sh v e, UVecTarget tr tslr L sh v2 e, Load slr SH tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr L sh v v2 e | |
| (UVecSource r slr L sh v e, UVecTarget tr tslr L sh v2 e, Load slr L tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr L sh v v2 e | |
| (Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e | |
| (Shape sh, Vector v e, NFData e) => UVecSource (SE MB) MB L sh v e | |
| (Shape sh, Vector v e, NFData e) => UVecSource (SE B) B L sh v e | |
| Shape sh => NFData (UArray D L sh a) | |
| Shape sh => NFData (UArray FS L sh e) | |
| Shape sh => NFData (UArray F L sh a) | |
| (Shape sh, NFData a) => NFData (UArray MB L sh a) | |
| (Shape sh, NFData a) => NFData (UArray B L sh a) |
General shape load type index. UArrays with SH load type index
specialize index and write and leave linearIndex and linearWrite
functions defined by default.
Type-level distinction between Linear and SHaped arrays
is aimed to avoid integral division operations while looping
through composite (Dim2, Dim3) indices.
Integral division is very expensive operation even on modern CPUs.
Instances
| Shape sh => PreferredWorkIndex SH sh sh | |
| Shape sh => UTarget DT SH sh a | |
| Shape sh => USource D SH sh a | |
| Shape sh => Regular DT SH sh a | |
| Shape sh => Regular D SH sh a | |
| Shape sh => DefaultFusion D D SH sh | |
| Shape sh => DefaultIFusion D SH D SH sh | |
| Shape sh => DefaultIFusion D L D SH sh | |
| Shape sh => DefaultIFusion FS L D SH sh | |
| Shape sh => DefaultIFusion F L D SH sh | |
| Shape sh => DefaultIFusion MB L D SH sh | |
| Shape sh => DefaultIFusion B L D SH sh | |
| Shape sh => IFusion r l D SH sh | |
| (Shape sh, Vector v e) => UVecSource D D SH sh v e | |
| (Shape sh, Vector v e) => VecRegular D D SH sh v e | |
| Load r SH tr SH sh a => RangeLoad r SH tr SH sh a | |
| Load r L tr SH sh a => RangeLoad r L tr SH sh a | |
| Load r SH tr L sh a => RangeLoad r SH tr L sh a | |
| (USource r SH sh a, UTarget tr SH sh a) => Load r SH tr SH sh a | |
| (USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a | |
| (USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a | |
| (VecLoad r slr SH tr tslr SH sh v v2 e, RangeLoad slr SH tslr SH sh e) => RangeVecLoad r slr SH tr tslr SH sh v v2 e | |
| (VecLoad r slr L tr tslr SH sh v v2 e, RangeLoad slr L tslr SH sh e) => RangeVecLoad r slr L tr tslr SH sh v v2 e | |
| (VecLoad r slr SH tr tslr L sh v v2 e, RangeLoad slr SH tslr L sh e) => RangeVecLoad r slr SH tr tslr L sh v v2 e | |
| (UVecSource r slr SH sh v e, UVecTarget tr tslr SH sh v2 e, Load slr SH tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr SH sh v v2 e | |
| (UVecSource r slr L sh v e, UVecTarget tr tslr SH sh v2 e, Load slr L tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr SH sh v v2 e | |
| (UVecSource r slr SH sh v e, UVecTarget tr tslr L sh v2 e, Load slr SH tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr L sh v v2 e | |
| (DefaultIFusion r l D SH sh, IFusion (SE r) l D SH sh) => DefaultIFusion (SE r) l D SH sh | |
| Shape sh => NFData (UArray DT SH sh a) | |
| Shape sh => NFData (UArray D SH sh a) |