yarr-0.9.1: Yet another array library

Safe HaskellNone

Data.Yarr.Base

Contents

Description

Core type system

Synopsis

General Regular classes

class (NFData (UArray r l sh a), Shape sh) => Regular r l sh a whereSource

This class generalizes USource and UTarget.

Paramenters:

  • r - representation,
  • l - load type,
  • sh - shape,
  • a - element type.

Counterpart for arrays of vectors: VecRegular.

Associated Types

data UArray r l sh a Source

Methods

extent :: UArray r l sh a -> shSource

Returns the extent an the array.

touchArray :: UArray r l sh a -> IO ()Source

Calling this function on foreign array (F) ensures it is still alive (GC haven't picked it). In other manifest representations, the function defined as return (). touchArray is lifted to top level in class hierarchy because in fact foreign representation is the heart of the library.

force :: UArray r l sh a -> IO ()Source

O(1) Ensures that array and all it's real manifest sources are fully evaluated. This function is not for people, it is for GHC compiler.

Default implementation: force arr = arr `deepseq` return ()

Instances

Shape sh => Regular DT SH sh a 
Shape sh => Regular D SH 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 => Regular CV CVL sh a 
Regular r l sh a => Regular (CHK r) l sh a 
(Regular r l sh e, Vector v e) => Regular (SE r) l sh (v e) 

class (Regular r l sh (v e), Regular slr l sh e, Vector v e) => VecRegular r slr l sh v e | r -> slr whereSource

Class for arrays of vectors.

Paramenters:

  • r - (entire) representation. Associated array type for this class is UArray r sh (v e).
  • slr - slice representation
  • l - load type
  • sh - shape
  • v - vector type
  • e - vector (not array) element type. Array element type is entire vector: (v e).

Counterpart for "simple" arrays: Regular.

Methods

slices :: UArray r l sh (v e) -> VecList (Dim v) (UArray slr l sh e)Source

O(1) Array of vectors -> vector of arrays. Think about this function as shallow unzip from Prelude. Slices are views of an underlying array.

Example:

 let css = slices coords
     xs = css ! 0
     ys = css ! 1

Instances

(Shape sh, Vector v e) => VecRegular D D SH 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 
(Regular r l sh e, Shape sh, Vector v e) => VecRegular (SE r) r l sh v e 
VecRegular r slr l sh v e => VecRegular (CHK r) (CHK slr) l sh v e 

class NFData a where

A class of types that can be fully evaluated.

Methods

rnf :: a -> ()

rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return '()'.

The default implementation of rnf is

 rnf a = a `seq` ()

which may be convenient when defining instances for data types with no unevaluated fields (e.g. enumerations).

Instances

NFData Bool 
NFData Char 
NFData Double 
NFData Float 
NFData Int 
NFData Int8 
NFData Int16 
NFData Int32 
NFData Int64 
NFData Integer 
NFData Word 
NFData Word8 
NFData Word16 
NFData Word32 
NFData Word64 
NFData () 
NFData Version 
NFData a => NFData [a] 
(Integral a, NFData a) => NFData (Ratio a) 
NFData (Fixed a) 
(RealFloat a, NFData a) => NFData (Complex a) 
NFData a => NFData (Maybe a) 
NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

(NFData a, NFData b) => NFData (Either a b) 
(NFData a, NFData b) => NFData (a, b) 
(Ix a, NFData a, NFData b) => NFData (Array a b) 
(Arity n, NFData e) => NFData (VecList n e) 
(NFData a, NFData b, NFData c) => NFData (a, b, c) 
(NFData a, NFData b, NFData c, NFData d) => NFData (a, b, c, d) 
Shape sh => NFData (UArray DT SH sh a) 
Shape sh => NFData (UArray D SH sh a) 
Shape sh => NFData (UArray D L sh a) 
(NFData (UArray r l sh e), Shape sh, Vector v e) => NFData (UArray (SE r) l sh (v e)) 
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) 
NFData (UArray r l sh a) => NFData (UArray (CHK r) l sh a) 
Shape sh => NFData (UArray CV CVL sh a) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 
(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 

deepseq :: NFData a => a -> b -> b

deepseq: fully evaluates the first argument, before returning the second.

The name deepseq is used to illustrate the relationship to seq: where seq is shallow in the sense that it only evaluates the top level of its argument, deepseq traverses the entire data structure evaluating it completely.

deepseq can be useful for forcing pending exceptions, eradicating space leaks, or forcing lazy I/O to happen. It is also useful in conjunction with parallel Strategies (see the parallel package).

There is no guarantee about the ordering of evaluation. The implementation may evaluate the components of the structure in any order or in parallel. To impose an actual order on evaluation, use pseq from Control.Parallel in the parallel package.

Shape class

class (Eq sh, Bounded sh, Show sh, NFData sh) => Shape sh Source

Class for column-major, regular composite array indices.

Instances

Fixed vector

type family Dim v :: *

Size of vector expressed as type-level natural.

class Arity n

Type class for handling n-ary functions.

Instances

Arity Z 
Arity n => Arity (S n) 

data Fun n a b

Newtype wrapper which is used to make Fn injective.

Instances

Arity n => Functor (Fun n a) 

class Arity (Dim v) => Vector v a

Type class for vectors with fixed length.

data VecList n a

Vector based on the lists. Not very useful by itself but is necessary for implementation.

Instances

Arity n => VectorN VecList n a 
Arity n => Vector (VecList n) a 
Eq a => Eq (VecList n a) 
Show a => Show (VecList n a) 
(Arity n, NFData e) => NFData (VecList n e) 

Source classes

class Regular r l sh a => USource r l sh a whereSource

Class for arrays which could be indexed.

It's functions are unsafe: you must call touchArray after the last call. Fortunately, you will hardly ever need to call them manually.

Minimum complete defenition: index or linearIndex.

Counterpart for arrays of vectors: UVecSource

Methods

index :: UArray r l sh a -> sh -> IO aSource

Shape, genuine monadic indexing.

In Yarr arrays are always zero-indexed and multidimensionally square. Maximum index is (extent arr).

Default implementation: index arr sh = linearIndex arr $ toLinear (extent arr) sh

linearIndex :: UArray r l sh a -> Int -> IO aSource

"Surrogate" linear index. For Dim1 arrays index == linearIndex.

Default implementation: linearIndex arr i = index arr $ fromLinear (extent arr) i

Instances

Shape sh => USource D SH 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 => USource CV CVL sh a 
USource r l sh a => USource (CHK r) l sh a 
(USource r l sh e, Vector v e) => USource (SE r) l sh (v e) 

class (VecRegular r slr l sh v e, USource r l sh (v e), USource slr l sh e) => UVecSource r slr l sh v e Source

Class for arrays of vectors which could be indexed. The class doesn't need to define functions, it just gathers it's dependencies.

Counterpart for "simple" arrays: USource.

Instances

(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, Storable e) => UVecSource F FS L 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 
UVecSource r slr l sh v e => UVecSource (CHK r) (CHK slr) l sh v e 

Fusion

class Fusion r fr l => DefaultFusion r fr l | 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

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.

class Fusion r fr l whereSource

Generalized, non-injective version of DefaultFusion. Used internally.

Minimum complete defenition: fmapM, fzip2M, fzip3M and fzipM.

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

Methods

fmapSource

Arguments

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

.

-> UArray r l sh a 
-> UArray fr l sh b 

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

fzip2Source

Arguments

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

.

-> UArray r l sh a 
-> UArray r l sh b 
-> UArray fr l sh c 

fzip2MSource

Arguments

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

.

-> UArray r l sh a 
-> UArray r l sh b 
-> UArray fr l sh c 

fzip3Source

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)

.

-> UArray r l sh a 
-> UArray r l sh b 
-> UArray r l sh c 
-> UArray fr l sh d 

fzip3MSource

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)

.

-> UArray r l sh a 
-> UArray r l sh b 
-> UArray r l sh c 
-> UArray fr l sh d 

fzipSource

Arguments

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

.

-> VecList n (UArray r l sh a) 
-> UArray fr l sh b 

fzipMSource

Arguments

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

.

-> VecList n (UArray r l sh a) 
-> UArray fr l sh b 

Instances

Manifest and Target classes

class Regular tr tl sh a => UTarget tr tl sh a whereSource

Class for mutable arrays.

Just like for USource, it's function are unsafe and require calling touchArray after the last call.

Minimum complete defenition: write or linearWrite.

Counterpart for arrays of vectors: UVecTarget

Methods

write :: UArray tr tl sh a -> sh -> a -> IO ()Source

Shape, genuine monadic writing.

Default implementation: write tarr sh = linearWrite tarr $ toLinear (extent tarr) sh

linearWrite :: UArray tr tl sh a -> Int -> a -> IO ()Source

Fast (usually), linear indexing. Intented to be used internally.

Default implementation: linearWrite tarr i = write tarr $ fromLinear (extent tarr) i

Instances

Shape sh => UTarget DT SH sh a 
(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 
UTarget tr tl sh a => UTarget (CHK tr) tl sh a 
(UTarget tr tl sh e, Vector v e) => UTarget (SE tr) tl sh (v e) 

class (USource r l sh a, UTarget mr l sh a) => Manifest r mr l sh a | r -> mr, mr -> r whereSource

Class for arrays which could be created. It combines a pair of representations: freezed and mutable (raw). This segregation is lifted from Boxed representation and, in the final, from GHC system of primitive arrays.

Parameters:

  • r - freezed array representation.
  • mr - mutable, raw array representation
  • l - load type index, common for both representations
  • sh - shape of arrays
  • a - element type

Methods

new :: sh -> IO (UArray mr l sh a)Source

O(1) Creates and returns mutable array of the given shape.

freeze :: UArray mr l sh a -> IO (UArray r l sh a)Source

O(1) Freezes mutable array and returns array which could be indexed.

thaw :: UArray r l sh a -> IO (UArray mr l sh a)Source

O(1) Thaws freezed array and returns mutable version.

Instances

(Shape sh, Storable a) => Manifest F F L sh a 
(Shape sh, NFData a) => Manifest B MB L sh a 
Manifest r mr l sh a => Manifest (CHK r) (CHK mr) l sh a 
(Manifest r mr l sh e, Vector v e) => Manifest (SE r) (SE mr) l sh (v e) 

class (VecRegular tr tslr tl sh v e, UTarget tr tl sh (v e), UTarget tslr tl sh e) => UVecTarget tr tslr tl sh v e Source

Class for mutable arrays of vectors. The class doesn't need to define functions, it just gathers it's dependencies.

Counterpart for "simple" arrays: UTarget.

Instances

(Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e 
(UTarget tr tl sh e, Vector v e) => UVecTarget (SE tr) tr tl sh v e 
UVecTarget tr tslr l sh v e => UVecTarget (CHK tr) (CHK tslr) l sh v e