yarr-1.2.3: Yet another array library

Safe HaskellNone

Data.Yarr.Repr.Delayed

Contents

Synopsis

Delayed source

data D Source

Delayed representation is a wrapper for arbitrary indexing function.

UArray D L sh a instance holds linear getter ((Int -> IO a)), and UArray D SH sh a - shaped, "true" (sh -> IO a) index, respectively.

Delayed arrays are most common recipients for fusion operations.

Instances

DefaultFusion D D SH 
DefaultFusion D D L 
DefaultFusion FS D L 
DefaultFusion F D L 
DefaultFusion MB D L 
DefaultFusion B D L 
Fusion r D SH 
Fusion r D L 
Shape sh => USource D SH sh a 
Shape sh => USource D L sh a 
Shape sh => Regular D SH sh a 
Shape sh => Regular D L sh a 
(Shape sh, Vector v e) => UVecSource D D SH sh v e 
(Shape sh, Vector v e) => UVecSource D D L sh v e 
(Shape sh, Vector v e) => VecRegular D D SH sh v e 
(Shape sh, Vector v e) => VecRegular D D L sh v e 
(DefaultFusion r D l, Fusion (SE r) D l) => DefaultFusion (SE r) D l 
Shape sh => NFData (UArray D SH sh a) 
Shape sh => NFData (UArray D L sh a) 

Delayed target

data DT Source

In opposite to Delayed (source) Delayed Target holds abstract writing function: (sh -> a -> IO ()). It may be used to perform arbitrarily tricky things, because no one obliges you to indeed write an element inside wrapped function.

Instances

Shape sh => UTarget DT SH sh a 
Shape sh => Regular DT SH sh a 
Shape sh => NFData (UArray DT SH sh a) 

There are also LinearDelayed, ShapeDelayed and ShapeDelayedTarget UArray family constructors, which aren't presented in the docs because Haddock doesn't support associated family constructors.

See source of Data.Yarr.Repr.Delayed module.

Misc

data L Source

Linear load type index. UArrays with L load type index define linearIndex and linearWrite and leave index and write functions defined by default.

Instances

DefaultFusion D D L 
DefaultFusion FS D L 
DefaultFusion F D L 
DefaultFusion MB D L 
DefaultFusion B D L 
Fusion r D L 
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 
(Shape sh, Storable a) => Manifest F F L sh a 
(Shape sh, NFData a) => Manifest B MB L sh a 
(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) 

data SH Source

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

DefaultFusion D D SH 
Fusion r D SH 
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, 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 
Shape sh => NFData (UArray DT SH sh a) 
Shape sh => NFData (UArray D SH sh a) 

fromFunctionSource

Arguments

:: Shape sh 
=> sh

Extent of array

-> (sh -> IO a)

Indexing function

-> UArray D SH sh a

Result array

Wrap indexing function into delayed representation.

Use this function carefully, don't implement through it something that has specialized implementation in the library (mapping, zipping, etc).

Suitable to obtain arrays of constant element, of indices (fromFunction sh id), and so on.

delay :: (USource r l sh a, USource D l sh a, Fusion r D l) => UArray r l sh a -> UArray D l sh aSource

Load type preserving wrapping arbirtary array into Delayed representation.

delayShaped :: USource r l sh a => UArray r l sh a -> UArray D SH sh aSource

Wraps (index arr) into Delayed representation. Normally you shouldn't need to use this function. It may be dangerous for performance, because preferred Loading type of source array is ignored.