yarr-1.3.2: Yet another array library

Safe HaskellNone

Data.Yarr.Flow

Contents

Description

Dataflow (fusion operations)

Synopsis

Basic fusion

class Fusion r fr l sh => DefaultFusion r fr l sh | r -> fr whereSource

This class abstracts pair of array types, which could be (preferably should be) mapped (fused) one to another. Injective version of Fusion class.

Parameters:

  • r - source array representation. It determines result representation.
  • fr (fused repr) - result (fused) array representation. Result array isn't indeed presented in memory, finally it should be computed or Loaded to Manifest representation.
  • l - load type, common for source and fused arrays
  • sh - shape of arrays

All functions are already defined, using non-injective versions from Fusion class.

The class doesn't have vector counterpart, it's role play top-level functions from Data.Yarr.Repr.Separate module.

Methods

dmapSource

Arguments

:: (USource r l sh a, USource fr l sh b) 
=> (a -> b)

Element mapper function

-> UArray r l sh a

Source array

-> UArray fr l sh b

Result array

O(1) Pure element mapping.

Main basic "map" in Yarr.

dmapMSource

Arguments

:: (USource r l sh a, USource fr l sh b) 
=> (a -> IO b)

Monadic element mapper function

-> UArray r l sh a

Source array

-> UArray fr l sh b

Result array

O(1) Monadic element mapping.

dzip2Source

Arguments

:: (USource r l sh a, USource r l sh b, USource fr l sh c) 
=> (a -> b -> c)

Pure element zipper function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray fr l sh c

Fused result array

O(1) Zipping 2 arrays of the same type indexes and shapes.

Example:

 let productArr = dzip2 (*) arr1 arr2

dzip2MSource

Arguments

:: (USource r l sh a, USource r l sh b, USource fr l sh c) 
=> (a -> b -> IO c)

Monadic element zipper function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray fr l sh c

Result array

O(1) Monadic version of dzip2 function.

dzip3Source

Arguments

:: (USource r l sh a, USource r l sh b, USource r l sh c, USource fr l sh d) 
=> (a -> b -> c -> d)

Pure element zipper function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray r l sh c

3rd source array

-> UArray fr l sh d

Result array

O(1) Zipping 3 arrays of the same type indexes and shapes.

dzip3MSource

Arguments

:: (USource r l sh a, USource r l sh b, USource r l sh c, USource fr l sh d) 
=> (a -> b -> c -> IO d)

Monadic element zipper function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray r l sh c

3rd source array

-> UArray fr l sh d

Fused result array

O(1) Monadic version of dzip3 function.

dzipSource

Arguments

:: (USource r l sh a, USource fr l sh b, Arity n, n ~ S n0) 
=> Fun n a b

Wrapped function positionally accepts elements from source arrays and emits element for fused array

-> VecList n (UArray r l sh a)

Source arrays

-> UArray fr l sh b

Result array

O(1) Generalized element zipping with pure function. Zipper function is wrapped in Fun for injectivity.

dzipMSource

Arguments

:: (USource r l sh a, USource fr l sh b, Arity n, n ~ S n0) 
=> Fun n a (IO b)

Wrapped monadic zipper

-> VecList n (UArray r l sh a)

Source arrays

-> UArray fr l sh b

Result array

O(1) Monadic version of dzip function.

Instances

class IFusion r l fr fl sh => DefaultIFusion r l fr fl sh | r l -> fr whereSource

Like DefaultFusion, this class abstracts the pair array types, which should be fused one to another on maps and zips which accept index of element (several elements for zips) in array (arrays).

Parameters:

  • r - source array representation. Determines result representation.
  • l - source load type
  • fr (fused repr) - result (fused) array representation. Result array isn't indeed presented in memory, finally it should be computed or Loaded to Manifest representation.
  • fl - result, "shaped" load type
  • sh - shape of arrays

All functions are already defined, using non-injective versions from IFusion class.

The class doesn't have vector counterpart.

Methods

imapSource

Arguments

:: (USource r l sh a, USource fr fl sh b) 
=> (sh -> a -> b)

Indexed mapping function

-> UArray r l sh a

Source array

-> UArray fr fl sh b

Fused result array

O(1) Pure element mapping with array index.

imapMSource

Arguments

:: (USource r l sh a, USource fr fl sh b) 
=> (sh -> a -> IO b)

Indexed monadic mapping function

-> UArray r l sh a

Source array

-> UArray fr fl sh b

Result fused array

O(1) Monadic element mapping with index.

izip2Source

Arguments

:: (USource r l sh a, USource r l sh b, USource fr fl sh c) 
=> (sh -> a -> b -> c)

Indexed zipping function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray fr fl sh c

Fused result array

O(1) Pure zipping of 2 arrays with index.

izip2MSource

Arguments

:: (USource r l sh a, USource r l sh b, USource fr fl sh c) 
=> (sh -> a -> b -> IO c)

Indexed monadic zipping function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray fr fl sh c

Fused result array

O(1) Monadic zipping of 2 arrays with index.

izip3Source

Arguments

:: (USource r l sh a, USource r l sh b, USource r l sh c, USource fr fl sh d) 
=> (sh -> a -> b -> c -> d)

Indexed zipping function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray r l sh c

3rd source array

-> UArray fr fl sh d

Fused result array

O(1) Pure zipping of 3 arrays with index.

izip3MSource

Arguments

:: (USource r l sh a, USource r l sh b, USource r l sh c, USource fr fl sh d) 
=> (sh -> a -> b -> c -> IO d)

Indexed monadic zipping function

-> UArray r l sh a

1st source array

-> UArray r l sh b

2nd source array

-> UArray r l sh c

3rd source array

-> UArray fr fl sh d

Fused result array

O(1) Monadic zipping of 3 arrays with index.

izipSource

Arguments

:: (USource r l sh a, USource fr fl sh b, Arity n, n ~ S n0) 
=> (sh -> Fun n a b)

Accepts index in array and returns wrapped zipper, which positionally accepts elements from source arrays and emits element for the result array

-> VecList n (UArray r l sh a)

Bunch of source arrays

-> UArray fr fl sh b

Result fused array

O(1) Generalized pure element zipping with index in arrays. Zipper function is wrapped in Fun for injectivity.

izipMSource

Arguments

:: (USource r l sh a, USource fr fl sh b, Arity n, n ~ S n0) 
=> (sh -> Fun n a (IO b))

Monadic indexed zipper

-> VecList n (UArray r l sh a)

Source arrays

-> UArray fr fl sh b

Result fused array

O(1) Monadic version of izip function.

Instances

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 => DefaultIFusion CV CVL CV CVL sh 
(DefaultIFusion r l D SH sh, IFusion (SE r) l D SH sh) => DefaultIFusion (SE r) l D SH sh 

Delayed flow and zipping shortcuts

dzipWithSource

Arguments

:: (USource r1 l sh a, DefaultFusion r1 D l sh, USource D l sh a, USource r2 l sh b, DefaultFusion r2 D l sh, USource D l sh b, USource D l sh c, DefaultFusion D D l sh) 
=> (a -> b -> c)

Pure zipping function

-> UArray r1 l sh a

1st source array

-> UArray r2 l sh b

2nd source array

-> UArray D l sh c

Fused result array

O(1) Generalized zipping of 2 arrays.

Main basic "zipWith" in Yarr.

Although sighature of this function has extremely big predicate, it is more permissible than dzip2 counterpart, because source arrays shouldn't be of the same type.

Implemented by means of delay function (source arrays are simply delayed before zipping).

dzipWith3Source

Arguments

:: (USource r1 l sh a, DefaultFusion r1 D l sh, USource D l sh a, USource r2 l sh b, DefaultFusion r2 D l sh, USource D l sh b, USource r3 l sh c, DefaultFusion r3 D l sh, USource D l sh c, USource D l sh d, DefaultFusion D D l sh) 
=> (a -> b -> c -> d)

Pure zipping function

-> UArray r1 l sh a

1st source array

-> UArray r2 l sh b

2nd source array

-> UArray r3 l sh c

3rd source array

-> UArray D l sh d

Result array

O(1) Generalized zipping of 3 arrays, which shouldn't be of the same representation type.

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

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 => DefaultFusion D D SH sh 
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 => 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) => 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 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 
Shape sh => NFData (UArray D SH sh a) 
Shape sh => NFData (UArray D L 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 aSource

Load type preserving wrapping arbirtary array into Delayed representation.

Vector fusion

data SE r Source

SEparate meta array representation. Internally SEparate arrays hold vector of it's slices (so, slices is just getter for them).

Mostly useful for:

  • Separate in memory manifest Foreign arrays ("Unboxed" arrays in vector/repa libraries terms).
  • Element-wise vector array fusion (see group of dmapElems functions).

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)) 

dmapElemsSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh, Vector v2 b, Dim v ~ Dim v2) 
=> VecList (Dim v) (a -> b)

Vector of mapper functions

-> UArray r l sh (v a)

Source array of vectors

-> UArray (SE fslr) l sh (v2 b)

Fused array

O(1) Injective element-wise fusion (mapping).

Example:

 let domainHSVImage =
         dmapElems (vl_3 (* 360) (* 100) (* 100))
                   normedHSVImage

Also, used internally to define mapElems function.

dmapElemsMSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh, Vector v2 b, Dim v ~ Dim v2) 
=> VecList (Dim v) (a -> IO b)

Elemen-wise vector of monadic mappers

-> UArray r l sh (v a)

Source array of vectors

-> UArray (SE fslr) l sh (v2 b)

Result array

O(1) Monadic vesion of dmapElems function.

dzipElems2Source

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, VecRegular r slr l sh v b, USource slr l sh b, USource fslr l sh c, DefaultFusion slr fslr l sh, Vector v c) 
=> VecList (Dim v) (a -> b -> c)

.

-> UArray r l sh (v a) 
-> UArray r l sh (v b) 
-> UArray (SE fslr) l sh (v c) 

dzipElems2MSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, VecRegular r slr l sh v b, USource slr l sh b, USource fslr l sh c, DefaultFusion slr fslr l sh, Vector v c) 
=> VecList (Dim v) (a -> b -> IO c)

.

-> UArray r l sh (v a) 
-> UArray r l sh (v b) 
-> UArray (SE fslr) l sh (v c) 

dzipElems3Source

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, VecRegular r slr l sh v b, USource slr l sh b, VecRegular r slr l sh v c, USource slr l sh c, USource fslr l sh d, DefaultFusion slr fslr l sh, Vector v d) 
=> VecList (Dim v) (a -> b -> c -> d)

.

-> UArray r l sh (v a) 
-> UArray r l sh (v b) 
-> UArray r l sh (v c) 
-> UArray (SE fslr) l sh (v d) 

dzipElems3MSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, VecRegular r slr l sh v b, USource slr l sh b, VecRegular r slr l sh v c, USource slr l sh c, USource fslr l sh d, DefaultFusion slr fslr l sh, Vector v d) 
=> VecList (Dim v) (a -> b -> c -> IO d)

.

-> UArray r l sh (v a) 
-> UArray r l sh (v b) 
-> UArray r l sh (v c) 
-> UArray (SE fslr) l sh (v d) 

dzipElemsSource

Arguments

:: (Vector v2 b, Arity m, m ~ S m0, VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh) 
=> VecList (Dim v2) (Fun m a b)

Vector of wrapped m-ary element-wise zippers

-> VecList m (UArray r l sh (v a))

Vector of source arrays of vectors

-> UArray (SE fslr) l sh (v2 b)

Fused result array

O(1) Generalized element-wise zipping of several arrays of vectors.

dzipElemsMSource

Arguments

:: (Vector v2 b, Arity m, m ~ S m0, VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh) 
=> VecList (Dim v2) (Fun m a (IO b))

Vector of wrapped m-ary element-wise monadic zippers

-> VecList m (UArray r l sh (v a))

Vector of source arrays of vectors

-> UArray (SE fslr) l sh (v2 b)

Result array

O(1) Generalized monadic element-wise zipping of several arrays of vectors

High level shortcuts

traverseSource

Arguments

:: (USource r l sh a, Shape sh') 
=> (sh -> sh')

Function to produce result extent from source extent.

-> ((sh -> IO a) -> sh' -> IO b)

Function to produce elements of result array. Passed a lookup function to get elements of the source.

-> UArray r l sh a

Source array itself

-> UArray D SH sh' b

Result array

O(1) Function from repa.

zipElemsSource

Arguments

:: (Vector v a, USource r l sh (v a), USource fr l sh b, DefaultFusion r fr l sh) 
=> Fn (Dim v) a b

Unwrapped n-ary zipper function

-> UArray r l sh (v a)

Source array of vectors

-> UArray fr l sh b

Result array

O(1) Function for in-place zipping vector elements.

Always true:

zipElems f arr == dzip (Fun f) (slices arr)

Example:

let φs = zipElems (flip atan2) coords

mapElemsSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh, Vector v b) 
=> (a -> b)

Mapper function for all elements

-> UArray r l sh (v a)

Source array of vectors

-> UArray (SE fslr) l sh (v b)

Fused array of vectors

O(1) Maps elements of vectors in array uniformly. Don't confuse with dmapElems, which accepts a vector of mapper for each slice.

Typical use case -- type conversion:

 let floatImage :: UArray F Dim2 Float
     floatImage = mapElems fromIntegral word8Image

mapElemsMSource

Arguments

:: (VecRegular r slr l sh v a, USource slr l sh a, USource fslr l sh b, DefaultFusion slr fslr l sh, Vector v b) 
=> (a -> IO b)

Monadic mapper for all vector elements

-> UArray r l sh (v a)

Source array of vectors

-> UArray (SE fslr) l sh (v b)

Fused array of vectors

O(1) Monadic version of mapElems function. Don't confuse with dmapElemsM.

Example:

let domained = mapElemsM (clampM 0.0 1.0) floatImage

Cartesian products

cartProduct2 :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b) => (a -> b -> c) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray D SH Dim2 cSource

icartProduct2 :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b) => (Dim2 -> a -> b -> c) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray D SH Dim2 cSource

icartProduct2M :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b) => (Dim2 -> a -> b -> IO c) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray D SH Dim2 cSource

cartProduct3 :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b, USource r3 l3 Dim1 c) => (a -> b -> c -> d) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray r3 l3 Dim1 c -> UArray D SH Dim3 dSource

icartProduct3 :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b, USource r3 l3 Dim1 c) => (Dim3 -> a -> b -> c -> d) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray r3 l3 Dim1 c -> UArray D SH Dim3 dSource

icartProduct3M :: (USource r1 l1 Dim1 a, USource r2 l2 Dim1 b, USource r3 l3 Dim1 c) => (Dim3 -> a -> b -> c -> IO d) -> UArray r1 l1 Dim1 a -> UArray r2 l2 Dim1 b -> UArray r3 l3 Dim1 c -> UArray D SH Dim3 dSource