| Safe Haskell | None |
|---|
Data.Yarr
Contents
Description
Type system intro:
Regular is main type class in the library.
Like Source class in repa, it defines indexed type family: UArray.
Classes USource, for arrays which could be indexed, and UTarget,
for mutable arrays, inherit from Regular.
As in repa, arrays in Yarr are type-indexed.
UArray type family has 2 type indexes:
- representation index - the first type argument.
- load type index -
the second argument of the type family. Pair of load indexes,
from source and target array determines how arrays will be
loaded one to another. Load index is mostly internal thing.
See
Loadclass for details.
Rest 2 UArray parameters generalize Shape and element type.
VecRegular, UVecSource, UVecTarget are counterparts for arrays
of fixed-sized vectors.
These classes have 6 arguments: repr type index, slice repr type index,
load type index, shape, vector type, vector element.
Note: in the docs "vector" always stands for
fixed-size vector. Don't confuse with vector from vector library.
As in repa, there are several kinds of representations:
-
Manifestrepresentations:Foreign andBoxed withMB(Mutable Boxed). The difference betweenManifestandUTargetarrays is thatManifestarrays could be created (seenewfunction). For example,FS(Foreign Slice) is a slice representation forF. FS-arrays are mutable, but you can't create a slice, you should firstly allocate entireFarray. - Delayed, or fused representations:
Delayed andCV(ConVoluted). Arrays of these types aren't really exist in memory. Finally they should be loaded to manifest arrays. - View representations:
DT(Delayed Target) andFS. Useful for advanced hand-controlled flow operations. - Meta representations:
SEparate andCHK(CHecKed). Thery are parameterized with another representation index. Arrays of meta types play almost like their prototypes.SEglues several arrays into one array of vectors (array types withSEindex are always instances ofVecRegularclass).CHKis useful for debugging, it raises error on illegal indexing attempt. By default indexing is unchecked.
Representation choice:
Foreign is the main manifest representation.
"Unboxed" arrays of tuples from repa and vector libraries
may be emulated by ( type index,
but keep in mind that they are usually slower than vanilla foreign arrays,
because the latter are memory-local.
SE F)
How to load array into memory:
Currently there is only one option "out of the box" - to load image :)
See Data.Yarr.IO.Image module in yarr-image-io package.
Consider also Data.Yarr.IO.List module, although it is very slow way to obtain manifest array in memory.
How to map and zip arrays:
See DefaultFusion class and functions in Data.Yarr.Flow module.
Example:
let delayedVecLengths = zipElems (x y -> sqrt (x * x + y * y)) vecsHow to compute an array:
See Load class and its counterpart VecLoad, and compute function.
Typical use:
vecLengths <-compute(loadPfillcaps) delayedVecLengths
Working examples- https://github.com/leventov/yarr/tree/master/tests
How to write fast program:
- Read corresponding section in
repaguide: http://hackage.haskell.org/packages/archive/repa/3.2.3.1/doc/html/Data-Array-Repa.html - Write
INLINEpragmas to all functions, including curried shortcuts. For example in such case:let {myIndex =you should write:indexarr} in ...let {{-# INLINE myIndex #-};myIndex =indexarr} in ... - Although the library is highly generalized, target programs should be as as precise in types as possible. Don't neglect writing signatures for functions.
- Compilation flags:
-Odph -rtsopts -threaded -fno-liberate-case -funbox-strict-fields-fexpose-all-unfoldings -funfolding-keeness-factor1000-fsimpl-tick-factor=500 -fllvm -optlo-O3.
Abbreviations across the library:
In names:
-
U-,u-,unsafe-prefixes mean that: a) function parameters must conform special statically unchecked conditions, or b) it isn't OK just to call the function, you must do something else, call another function. All functions in type classes withU-prefix (USource,UTarget) are unsafe. -
d-prefix stands for "default". Typically function withd-prefix is carried version of the one without prefix. -
I-,i-prefixes for "indexed". Functions with this prefix accept array index before element itself. -
f-prefix means "fused". Used for functions fromFusionclass. -
-M, as usual, is for monadic versions of functions. However, if there isn't non-monadic version (the most part of core functions), the suffix is omitted. -
-Sand-Pare suffixes fromrepa, they indicate sequential and parallel versions of flow operation, respectively.
In signatures:
-
r,tr,mr- representation, target repr, manifest repr. For the first type index ofUArrayfamily. -
slr,tslr,mslr- slice representation, respectively -
l,tl- load index, for the second argument ofUArray -
sh- array shape:Dim1,Dim2, orDim3 -
v,v1,v2-Vectortype -
e,e2- vector element -
n,m-Arityof vector
- module Data.Yarr.Base
- type Dim1 = Int
- type Dim2 = (Int, Int)
- type Dim3 = (Int, Int, Int)
- newtype Fun n a b = Fun (Fn n a b)
- class Arity (Dim v) => Vector v a where
- newtype VecList n a = VecList [a]
- type N1 = S Z
- type N2 = S N1
- type N3 = S N2
- type N4 = S N3
- module Data.Yarr.Flow
- module Data.Yarr.Eval
- data F
- unsafeFromForeignPtr :: Shape sh => sh -> ForeignPtr a -> IO (UArray F L sh a)
- toForeignPtr :: Shape sh => UArray F L sh a -> ForeignPtr a
- data D
- fromFunction :: Shape sh => sh -> (sh -> IO a) -> UArray D SH sh a
- delay :: (USource r l sh a, USource D l sh a, Fusion r D l sh) => UArray r l sh a -> UArray D l sh a
- data SE r
- fromSlices :: (Regular r l sh e, Vector v e, Dim v ~ S n0) => VecList (Dim v) (UArray r l sh e) -> UArray (SE r) l sh (v e)
- unsafeMapSlices :: (USource r l sh a, Vector v a, USource r2 l2 sh2 b, Vector v b, Dim v ~ S n0) => (UArray r l sh a -> UArray r2 l2 sh2 b) -> UArray (SE r) l sh (v a) -> UArray (SE r2) l2 sh2 (v b)
Core type system
module Data.Yarr.Base
Shapes
Fixed Vector
class Arity (Dim v) => Vector v a where
Type class for vectors with fixed length.
newtype VecList n a
Vector based on the lists. Not very useful by itself but is necessary for implementation.
Constructors
| VecList [a] |
Dataflow (fusion operations)
module Data.Yarr.Flow
Loading and computing arrays
module Data.Yarr.Eval
Common representations
Foreign
Foreign representation is the heart of Yarr framework.
Internally it holds raw pointer (Ptr), which makes indexing
foreign arrays not slower than GHC's built-in primitive arrays,
but without freeze/thaw boilerplate.
Foreign arrays are very permissible, for example you can easily
use them as source and target of Loading operation simultaneously,
achieving old good in-place C-style array modifying:
loadSfill(dmapsqrtarr) arr
Foreign arrays are intented to hold all Storable types and
vectors of them (because there is a conditional instance of Storalbe
class for Vectors of Storables too).
Instances
| (Shape sh, Storable a) => UTarget F L sh a | |
| (Shape sh, Storable a) => USource F L sh a | |
| Shape sh => Regular F L sh a | |
| DefaultFusion F D L sh | |
| (Shape sh, Storable a) => Manifest F F L sh a | |
| Shape sh => DefaultIFusion F L D SH sh | |
| (Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e | |
| (Shape sh, Vector v e, Storable e) => UVecSource F FS L sh v e | |
| (Shape sh, Vector v e, Storable e) => VecRegular F FS L sh v e | |
| (Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e | |
| Shape sh => NFData (UArray F L sh a) |
unsafeFromForeignPtr :: Shape sh => sh -> ForeignPtr a -> IO (UArray F L sh a)Source
O(1) Wraps foreign ptr into foreign array.
The function is unsafe because it simply don't (and can't) check anything about correctness of produced array.
toForeignPtr :: Shape sh => UArray F L sh a -> ForeignPtr aSource
O(1) Returns pointer to memory block used by the given foreign array.
May be useful to reuse memory if you don't longer need the given array in the program:
brandNewData <-
unsafeFromForeignPtr ext (castForeignPtr (toForeignPtr arr))
Delayed
Delayed representation is a wrapper for arbitrary indexing function.
instance holds linear getter (UArray D L sh a(Int -> IO a)),
and - shaped, "true" UArray D SH sh a(sh -> IO a) index, respectively.
Delayed arrays are most common recipients for fusion operations.
Instances
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 ), and so on.
id
delay :: (USource r l sh a, USource D l sh a, Fusion r D l sh) => UArray r l sh a -> UArray D l sh aSource
Load type preserving wrapping arbirtary array into Delayed representation.
Separate
SEparate meta array representation. Internally SEparate arrays
hold vector of it's slices (so, slices is just getter for them).
Mostly useful for:
Instances
| (DefaultFusion r D l sh, Fusion (SE r) D l sh) => DefaultFusion (SE r) D l sh | |
| (DefaultIFusion r l D SH sh, IFusion (SE r) l D SH sh) => DefaultIFusion (SE r) l D SH sh | |
| (UTarget tr tl sh e, Vector v e) => UVecTarget (SE tr) tr tl sh v e | |
| (USource r l sh e, Vector v e) => UVecSource (SE r) r l sh v 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 | |
| (Regular r l sh e, Shape sh, Vector v e) => VecRegular (SE r) r l sh v 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 | |
| (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 | |
| (UTarget tr tl sh e, Vector v e) => UTarget (SE tr) tl sh (v e) | |
| (USource r l sh e, Vector v e) => USource (SE r) l sh (v e) | |
| (Regular r l sh e, Vector v e) => Regular (SE r) l sh (v e) | |
| (Manifest r mr l sh e, Vector v e) => Manifest (SE r) (SE mr) l sh (v e) | |
| (NFData (UArray r l sh e), Shape sh, Vector v e) => NFData (UArray (SE r) l sh (v e)) |
fromSlices :: (Regular r l sh e, Vector v e, Dim v ~ S n0) => VecList (Dim v) (UArray r l sh e) -> UArray (SE r) l sh (v e)Source
O(1) Glues several arrays of the same type into one separate array of vectors. All source arrays must be of the same extent.
Example:
let separateCoords = fromSlices (vl_3 xs ys zs)Arguments
| :: (USource r l sh a, Vector v a, USource r2 l2 sh2 b, Vector v b, Dim v ~ S n0) | |
| => (UArray r l sh a -> UArray r2 l2 sh2 b) | Slice mapper without restrictions |
| -> UArray (SE r) l sh (v a) | Source separate array |
| -> UArray (SE r2) l2 sh2 (v b) | Result separate array |
O(depends on mapper function) Maps slices of separate array "entirely".
This function is useful when operation over slices is not
element-wise (in that case you should use mapElems):
let blurredImage = unsafeMapSlices blur image
The function is unsafe because it doesn't check that slice mapper translates extents uniformly (though it is pure).