| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
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
- type LoadIndex l tl sh
- 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
type Threads = IO Int Source #
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 where Source #
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 typetr- target representation. Instance ofUTargetclass.tl- target load typesh- shape of arraysa- 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
type LoadIndex l tl sh Source #
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
loadP :: Fill (LoadIndex l tl sh) a -> Threads -> UArray r l sh a -> UArray tr tl sh a -> IO () Source #
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
loadS :: Fill (LoadIndex l tl sh) a -> UArray r l sh a -> UArray tr tl sh a -> IO () Source #
Instances
| (USource r SH sh a, UTarget tr SH sh a) => Load r SH tr SH sh a Source # | |
| (USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a Source # | |
| (USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a Source # | |
| (USource r L sh a, UTarget tr L sh a, WorkIndex sh Int) => Load r L tr L sh a Source # | |
class Load r l tr tl sh a => RangeLoad r l tr tl sh a where Source #
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
rangeLoadP :: Fill sh a -> Threads -> UArray r l sh a -> UArray tr tl sh a -> sh -> sh -> IO () Source #
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))
rangeLoadS :: Fill sh a -> UArray r l sh a -> UArray tr tl sh a -> sh -> sh -> IO () Source #
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 where Source #
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 representationslr- source slice representationl- source load typetr- target representationtslr- target slice representationtl- target load typesh- shape of arraysv- source vector typev2- target vector typee- vector element type, common for source and target arrays
Methods
loadSlicesP :: Fill (LoadIndex l tl sh) e -> Threads -> UArray r l sh (v e) -> UArray tr tl sh (v2 e) -> IO () Source #
O(n) Entirely, slice-wise loads vectors from source to target in parallel.
Example:
-- blurred and delayedBlurred are arrays of color components. loadSlicesPfillcapsdelayedBlurred blurred
loadSlicesS :: Fill (LoadIndex l tl sh) e -> UArray r l sh (v e) -> UArray tr tl sh (v2 e) -> IO () Source #
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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
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 Source #
This class extends VecLoad just like RangeLoad extends Load.
It abstracts slice-wise loading from one array type to
another in specified range.
Methods
rangeLoadSlicesP :: Fill sh e -> Threads -> UArray r l sh (v e) -> UArray tr tl sh (v2 e) -> sh -> sh -> IO () Source #
O(n) Loads vectors from source to target in specified range, slice-wise, in parallel.
rangeLoadSlicesS :: Fill sh e -> UArray r l sh (v e) -> UArray tr tl sh (v2 e) -> sh -> sh -> IO () Source #
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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
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
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 Source # | |
| Shape sh => UTarget DT SH sh a Source # | |
| Shape sh => USource D SH sh a Source # | |
| Shape sh => Regular DT SH sh a Source # | |
| Shape sh => Regular D SH sh a Source # | |
| Shape sh => DefaultFusion D D SH sh Source # | |
| Shape sh => DefaultIFusion D SH D SH sh Source # | |
| Shape sh => DefaultIFusion D L D SH sh Source # | |
| Shape sh => DefaultIFusion FS L D SH sh Source # | |
| Shape sh => DefaultIFusion F L D SH sh Source # | |
| Shape sh => DefaultIFusion MB L D SH sh Source # | |
| Shape sh => DefaultIFusion B L D SH sh Source # | |
| Shape sh => IFusion r l D SH sh Source # | |
| (Shape sh, Vector v e) => UVecSource D D SH sh v e Source # | |
| (Shape sh, Vector v e) => VecRegular D D SH sh v e Source # | |
| Load r SH tr SH sh a => RangeLoad r SH tr SH sh a Source # | |
| Load r L tr SH sh a => RangeLoad r L tr SH sh a Source # | |
| Load r SH tr L sh a => RangeLoad r SH tr L sh a Source # | |
| (USource r SH sh a, UTarget tr SH sh a) => Load r SH tr SH sh a Source # | |
| (USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a Source # | |
| (USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (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 Source # | |
| (DefaultIFusion r l D SH sh, IFusion (SE r) l D SH sh) => DefaultIFusion (SE r) l D SH sh Source # | |
| Shape sh => NFData (UArray DT SH sh a) # | |
| Shape sh => NFData (UArray D SH sh a) # | |
| data UArray DT SH Source # | |
| data UArray D SH Source # | |
| type LoadIndex SH SH sh Source # | |
| type LoadIndex SH L sh Source # | |
| type LoadIndex L SH sh Source # | |