massiv-0.2.8.0: Massiv (Массив) is an Array Library.

Copyright(c) Alexey Kuleshevich 2018
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array

Contents

Description

Massiv is a library, that allows creation and manipulation of arrays in parallel and sequentially. Depending on the representation (r), an Array r ix e will have certain properties that are unique to that particular representation, but all of them will share the same trait, that an array is simply a mapping from an index (ix) of an arbitrary dimension to an element (e) of some value. Which means that some of the array types are pretty classic and are represented by a contiguous chunk of memory reserved for the elements, namely arrays with Manifest representations:

  • B - The most basic type of array that can hold any type of element in a boxed form, i.e. each element is a pointer to the actual value, therefore it is also the slowest representation. Elements are kept in a Weak Head Normal Form (WHNF).
  • N - Similar to B, is also a boxed type, except it's elements are always kept in a Normal Form (NF). This property is very useful for parallel processing, i.e. when calling compute you do want all of your elements to be fully evaluated.
  • S - Is a type of array that is backed by pinned memory, therefore pointers to those arrays can be passed to FFI calls, because Garbage Collector (GC) is guaranteed not to move it. Elements must be an instance of Storable class. It is just as efficient as P and U arrays, except it is subject to fragmentation.
  • U - Unboxed representation. Elements must be an instance of Unbox class.
  • P - Array that can hold Haskell primitives, such as Int, Word, Double, etc. Any element must be an instance of Prim class.
  • M - General manifest array type, that any of the above representations can be converted to in constant time using toManifest.

While at the same time, there are arrays that only describe how values for it's elements can be computed, and have no memory overhead on their own.

  • D - delayed array that is a mere function from an index to an element. Crucial representation for fusing computation. Use computeAs in order to load array into Manifest representation.
  • DI - delayed interleaved array. Same as D, but performced better with unbalanced computation, when evaluation one element takes much longer than it's neighbor.
  • DW - delayed windowed array. This peculiar representation allows for very fast Stencil computation.

Other Array types:

  • L and LN - those types aren't particularly useful on their own, but because of their unique ability to be converted to and from nested lists in constant time, provide an amazing intermediary for list/array conversion.

Most of the Manifest arrays are capable of in-place mutation. Check out Data.Massiv.Array.Mutable module for available functionality.

Many of the function names exported by this package will clash with the ones from Prelude, hence it can be more convenient to import like this:

import Prelude as P
import Data.Massiv.Array as A
Synopsis

Construct

From a function

makeArray Source #

Arguments

:: Construct r ix e 
=> Comp

Computation strategy. Useful constructors are Seq and Par

-> Sz ix

Size of the result array. Negative values will result in an empty array.

-> (ix -> e)

Function to generate elements at a particular index

-> Array r ix e 

Create an Array. Resulting type either has to be unambiguously inferred or restricted manually, like in the example below.

>>> makeArray Seq (Sz (3 :. 4)) (\ (i :. j) -> if i == j then i else 0) :: Array D Ix2 Int
(Array D Seq (3 :. 4)
[ [ 0,0,0,0 ]
, [ 0,1,0,0 ]
, [ 0,0,2,0 ]
])

makeArrayR :: Construct r ix e => r -> Comp -> Sz ix -> (ix -> e) -> Array r ix e Source #

Just like makeArray but with ability to specify the result representation as an argument. Note the Unboxed type constructor in the below example.

>>> makeArrayR U Par (Sz (2 :> 3 :. 4)) (\ (i :> j :. k) -> i * i + j * j == k * k)
(Array U Par (2 :> 3 :. 4)
  [ [ [ True,False,False,False ]
    , [ False,True,False,False ]
    , [ False,False,True,False ]
    ]
  , [ [ False,True,False,False ]
    , [ False,False,False,False ]
    , [ False,False,False,False ]
    ]
  ])

makeVectorR :: Construct r Ix1 e => r -> Comp -> Sz1 -> (Ix1 -> e) -> Array r Ix1 e Source #

Same as makeArrayR, but restricted to 1-dimensional arrays.

singleton Source #

Arguments

:: Construct r ix e 
=> Comp

Computation strategy

-> e

The element

-> Array r ix e 

Create an Array with a single element.

Applicative

makeArrayA :: (Mutable r ix b, Applicative f) => Comp -> Sz ix -> (ix -> f b) -> f (Array r ix b) Source #

Similar to makeArray, but construct the array sequentially using an Applicative interface disregarding the supplied Comp.

Since: 0.2.6

makeArrayAR :: (Mutable r ix b, Applicative f) => r -> Comp -> Sz ix -> (ix -> f b) -> f (Array r ix b) Source #

Same as makeArrayA, but with ability to supply result array representation.

Since: 0.2.6

Enumeration

range :: Comp -> Int -> Int -> Array D Ix1 Int Source #

Create a vector with a range of Ints incremented by 1. range k0 k1 == rangeStep k0 k1 1

>>> range Seq 1 6
(Array D Seq (5)
  [ 1,2,3,4,5 ])
>>> range Seq (-2) 3
(Array D Seq (5)
  [ -2,-1,0,1,2 ])

rangeStep Source #

Arguments

:: Comp

Computation strategy

-> Int

Start

-> Int

Step (Can't be zero)

-> Int

End

-> Array D Ix1 Int 

Same as range, but with a custom step.

>>> rangeStep Seq 1 2 6
(Array D Seq (3)
  [ 1,3,5 ])

enumFromN Source #

Arguments

:: Num e 
=> Comp 
-> e

x - start value

-> Int

n - length of resulting vector.

-> Array D Ix1 e 

Same as enumFromStepN with step delta = 1.

>>> enumFromN Seq (5 :: Double) 3
(Array D Seq (3)
  [ 5.0,6.0,7.0 ])

enumFromStepN Source #

Arguments

:: Num e 
=> Comp 
-> e

x - start value

-> e

delta - step value

-> Int

n - length of resulting vector

-> Array D Ix1 e 

Create a vector with length n that has it's 0th value set to x and gradually increasing with step delta until the end. Similar to: fromList' Seq $ take n [x, x + delta ..]. Major difference is that fromList constructs an Array with manifest representation, while enumFromStepN is delayed.

>>> enumFromStepN Seq 1 (0.1 :: Double) 5
(Array D Seq (5)
  [ 1.0,1.1,1.2,1.3,1.4 ])

Expansion

expandWithin :: (IsIndexDimension ix n, Manifest r (Lower ix) a) => Dimension n -> Int -> (a -> Int -> b) -> Array r (Lower ix) a -> Array D ix b Source #

Function that expands an array to one with a higher dimension.

This is useful for constructing arrays where there is shared computation between multiple cells. The makeArray method of constructing arrays:

makeArray :: Construct r ix e => Comp -> ix -> (ix -> e) -> Array r ix e

...runs a function ix -> e at every array index. This is inefficient if there is a substantial amount of repeated computation that could be shared while constructing elements on the same dimension. The expand functions make this possible. First you construct an Array r (Lower ix) a of one fewer dimensions where a is something like Array r Ix1 a or Array r Ix2 a. Then you use expandWithin and a creation function a -> Int -> b to create an Array D Ix2 b or Array D Ix3 b respectfully.

Examples

Expand
>>> a = makeArrayR U Seq (Ix1 6) (+10) -- Imagine (+10) is some expensive function
>>> a
(Array U Seq (6)
  [ 10,11,12,13,14,15 ])
>>> expandWithin Dim1 5 (\ e j -> (j + 1) * 100 + e) a :: Array D Ix2 Int
(Array D Seq (6 :. 5)
  [ [ 110,210,310,410,510 ]
  , [ 111,211,311,411,511 ]
  , [ 112,212,312,412,512 ]
  , [ 113,213,313,413,513 ]
  , [ 114,214,314,414,514 ]
  , [ 115,215,315,415,515 ]
  ])
>>> expandWithin Dim2 5 (\ e j -> (j + 1) * 100 + e) a :: Array D Ix2 Int
(Array D Seq (5 :. 6)
  [ [ 110,111,112,113,114,115 ]
  , [ 210,211,212,213,214,215 ]
  , [ 310,311,312,313,314,315 ]
  , [ 410,411,412,413,414,415 ]
  , [ 510,511,512,513,514,515 ]
  ])

Since: 0.2.6

expandWithin' :: (Index ix, Manifest r (Lower ix) a) => Dim -> Int -> (a -> Int -> b) -> Array r (Lower ix) a -> Array D ix b Source #

Similar to expandWithin, except that dimension is specified at a value level, which means it will throw an exception on an invalid dimension.

Since: 0.2.6

expandOuter :: (Index ix, Manifest r (Lower ix) a) => Int -> (a -> Int -> b) -> Array r (Lower ix) a -> Array D ix b Source #

Similar to expandWithin, except it uses the outermost dimension.

Since: 0.2.6

expandInner :: (Index ix, Manifest r (Lower ix) a) => Int -> (a -> Int -> b) -> Array r (Lower ix) a -> Array D ix b Source #

Similar to expandWithin, except it uses the innermost dimension.

Since: 0.2.6

Compute

getComp :: Construct r ix e => Array r ix e -> Comp Source #

Get computation strategy of this array

setComp :: Construct r ix e => Comp -> Array r ix e -> Array r ix e Source #

Set computation strategy for this array

compute :: (Load r' ix e, Mutable r ix e) => Array r' ix e -> Array r ix e Source #

Ensure that Array is computed, i.e. represented with concrete elements in memory, hence is the Mutable type class restriction. Use setComp if you'd like to change computation strategy before calling compute

computeAs :: (Load r' ix e, Mutable r ix e) => r -> Array r' ix e -> Array r ix e Source #

Just as compute, but let's you supply resulting representation type as an argument.

Examples

Expand
>>> computeAs P $ range Seq 0 10
(Array P Seq (10)
  [ 0,1,2,3,4,5,6,7,8,9 ])

computeProxy :: (Load r' ix e, Mutable r ix e) => proxy r -> Array r' ix e -> Array r ix e Source #

Same as compute and computeAs, but let's you supply resulting representation type as a proxy argument.

Examples

Expand

Useful for cases when representation constructor isn't available for some reason:

>>> computeProxy (Nothing :: Maybe P) $ range Seq 0 10
(Array P Seq (10)
  [ 0,1,2,3,4,5,6,7,8,9 ])

Since: 0.1.1

computeSource :: forall r' r ix e. (Source r' ix e, Mutable r ix e) => Array r' ix e -> Array r ix e Source #

This is just like compute, but can be applied to Source arrays and will be a noop if resulting type is the same as the input.

computeWithStride :: (Load r' ix e, Mutable r ix e) => Stride ix -> Array r' ix e -> Array r ix e Source #

Same as compute, but with Stride.

computeWithStrideAs :: (Load r' ix e, Mutable r ix e) => r -> Stride ix -> Array r' ix e -> Array r ix e Source #

Same as computeWithStride, but with ability to specify resulting array representation.

clone :: Mutable r ix e => Array r ix e -> Array r ix e Source #

O(n) - Make an exact immutable copy of an Array.

convert :: (Manifest r' ix e, Mutable r ix e) => Array r' ix e -> Array r ix e Source #

O(n) - conversion between manifest types, except when source and result arrays are of the same representation, in which case it is an O(1) operation.

convertAs :: (Manifest r' ix e, Mutable r ix e) => r -> Array r' ix e -> Array r ix e Source #

Same as convert, but let's you supply resulting representation type as an argument.

convertProxy :: (Manifest r' ix e, Mutable r ix e) => proxy r -> Array r' ix e -> Array r ix e Source #

Same as convert and convertAs, but let's you supply resulting representation type as a proxy argument.

Since: 0.1.1

fromRaggedArray :: (Ragged r' ix e, Mutable r ix e) => Array r' ix e -> Either ShapeError (Array r ix e) Source #

Convert a ragged array into a usual rectangular shaped one.

fromRaggedArray' :: (Ragged r' ix e, Mutable r ix e) => Array r' ix e -> Array r ix e Source #

Same as fromRaggedArray, but will throw an error if its shape is not rectangular.

Size

size :: Size r ix e => Array r ix e -> Sz ix Source #

O(1) - Get the size of an array

elemsCount :: Size r ix e => Array r ix e -> Int Source #

O(1) - Get the number of elements in the array

isEmpty :: Size r ix e => Array r ix e -> Bool Source #

O(1) - Check if array has no elements.

Indexing

(!?) :: Manifest r ix e => Array r ix e -> ix -> Maybe e infixl 4 Source #

Infix version of index.

(!) :: Manifest r ix e => Array r ix e -> ix -> e infixl 4 Source #

Infix version of index'.

(??) :: Manifest r ix e => Maybe (Array r ix e) -> ix -> Maybe e infixl 4 Source #

O(1) - Lookup an element in the array, where array can itself be Nothing. This operator is useful when used together with slicing or other functions that return Maybe array:

>>> (fromList Seq [[[1,2,3]],[[4,5,6]]] :: Maybe (Array U Ix3 Int)) ??> 1 ?? (0 :. 2)
Just 6

index :: Manifest r ix e => Array r ix e -> ix -> Maybe e Source #

O(1) - Lookup an element in the array. Returns Nothing, when index is out of bounds, Just element otherwise.

index' :: Manifest r ix e => Array r ix e -> ix -> e Source #

O(1) - Lookup an element in the array. Throw an error if index is out of bounds.

defaultIndex :: Manifest r ix e => e -> Array r ix e -> ix -> e Source #

O(1) - Lookup an element in the array, while using default element when index is out of bounds.

borderIndex :: Manifest r ix e => Border e -> Array r ix e -> ix -> e Source #

O(1) - Lookup an element in the array. Use a border resolution technique when index is out of bounds.

evaluateAt :: Source r ix e => Array r ix e -> ix -> e Source #

This is just like index' function, but it allows getting values from delayed arrays as well as manifest. As the name suggests, indexing into a delayed array at the same index multiple times will cause evaluation of the value each time and can destroy the performace if used without care.

Mapping

map :: Source r ix e' => (e' -> e) -> Array r ix e' -> Array D ix e Source #

Map a function over an array

imap :: Source r ix e' => (ix -> e' -> e) -> Array r ix e' -> Array D ix e Source #

Map an index aware function over an array

Traversing

traverseA :: (Source r' ix a, Mutable r ix b, Applicative f) => (a -> f b) -> Array r' ix a -> f (Array r ix b) Source #

Traverse with an Applicative action over an array sequentially.

Since: 0.2.6

itraverseA :: (Source r' ix a, Mutable r ix b, Applicative f) => (ix -> a -> f b) -> Array r' ix a -> f (Array r ix b) Source #

Traverse with an Applicative index aware action over an array sequentially.

Since: 0.2.6

traverseAR :: (Source r' ix a, Mutable r ix b, Applicative f) => r -> (a -> f b) -> Array r' ix a -> f (Array r ix b) Source #

Same as traverseA, except with ability to specify representation.

Since: 0.2.6

itraverseAR :: (Source r' ix a, Mutable r ix b, Applicative f) => r -> (ix -> a -> f b) -> Array r' ix a -> f (Array r ix b) Source #

Same as itraverseA, except with ability to specify representation.

Since: 0.2.6

Monadic

Sequential

mapM :: (Source r' ix a, Mutable r ix b, Monad m) => (a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Map a monadic action over an array sequentially.

Since: 0.2.6

mapMR :: (Source r' ix a, Mutable r ix b, Monad m) => r -> (a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as mapM, except with ability to specify result representation.

Since: 0.2.6

forM :: (Source r' ix a, Mutable r ix b, Monad m) => Array r' ix a -> (a -> m b) -> m (Array r ix b) Source #

Same as mapM except with arguments flipped.

Since: 0.2.6

forMR :: (Source r' ix a, Mutable r ix b, Monad m) => r -> Array r' ix a -> (a -> m b) -> m (Array r ix b) Source #

Same as forM, except with ability to specify result representation.

Since: 0.2.6

imapM :: (Source r' ix a, Mutable r ix b, Monad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Map a monadic action over an array sequentially.

Since: 0.2.6

imapMR :: (Source r' ix a, Mutable r ix b, Monad m) => r -> (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as imapM, except with ability to specify result representation.

Since: 0.2.6

iforM :: (Source r' ix a, Mutable r ix b, Monad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as forM, except map an index aware action.

Since: 0.2.6

iforMR :: (Source r' ix a, Mutable r ix b, Monad m) => r -> (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as iforM, except with ability to specify result representation.

Since: 0.2.6

mapM_ :: (Source r ix a, Monad m) => (a -> m b) -> Array r ix a -> m () Source #

Map a monadic function over an array sequentially, while discarding the result.

Examples

Expand
>>> mapM_ print $ rangeStep 10 12 60
10
22
34
46
58

forM_ :: (Source r ix a, Monad m) => Array r ix a -> (a -> m b) -> m () Source #

Just like mapM_, except with flipped arguments.

Examples

Expand

Here is a common way of iterating N times using a for loop in an imperative language with mutation being an obvious side effect:

>>> :m + Data.IORef
>>> var <- newIORef 0 :: IO (IORef Int)
>>> forM_ (range 0 1000) $ \ i -> modifyIORef' var (+i)
>>> readIORef var
499500

imapM_ :: (Source r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m () Source #

Map a monadic index aware function over an array sequentially, while discarding the result.

Examples

Expand
>>> imapM_ (curry print) $ range 10 15
(0,10)
(1,11)
(2,12)
(3,13)
(4,14)

iforM_ :: (Source r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m () Source #

Just like imapM_, except with flipped arguments.

Parallelizable

mapIO :: (Source r' ix a, Mutable r ix b) => (a -> IO b) -> Array r' ix a -> IO (Array r ix b) Source #

Map an IO action over an Array. Underlying computation strategy is respected and will be parallelized when requested. Unfortunately no fusion is possible and new array will be create upon each call.

Since: 0.2.6

mapIO_ :: Source r b e => (e -> IO a) -> Array r b e -> IO () Source #

Similar to mapIO, but ignores the result of mapping action and does not create a resulting array, therefore it is faster. Use this instead of mapIO when result is irrelevant.

Since: 0.2.6

imapIO :: (Source r' ix a, Mutable r ix b) => (ix -> a -> IO b) -> Array r' ix a -> IO (Array r ix b) Source #

Same as mapIO but map an index aware action instead.

Since: 0.2.6

imapIO_ :: Source r ix e => (ix -> e -> IO a) -> Array r ix e -> IO () Source #

Same as mapIO_, but map an index aware action instead.

Since: 0.2.6

forIO :: (Source r' ix a, Mutable r ix b) => Array r' ix a -> (a -> IO b) -> IO (Array r ix b) Source #

Same as mapIO but with arguments flipped.

Since: 0.2.6

forIO_ :: Source r ix e => Array r ix e -> (e -> IO a) -> IO () Source #

Same as mapIO_ but with arguments flipped.

Since: 0.2.6

iforIO :: (Source r' ix a, Mutable r ix b) => Array r' ix a -> (ix -> a -> IO b) -> IO (Array r ix b) Source #

Same as imapIO but with arguments flipped.

Since: 0.2.6

iforIO_ :: Source r ix a => Array r ix a -> (ix -> a -> IO b) -> IO () Source #

Same as imapIO_ but with arguments flipped.

Since: 0.2.6

mapP_ :: Source r ix a => (a -> IO b) -> Array r ix a -> IO () Source #

Deprecated: In favor of mapIO_

Map an IO action, over an array in parallel, while discarding the result.

imapP_ :: Source r ix a => (ix -> a -> IO b) -> Array r ix a -> IO () Source #

Deprecated: In favor of imapIO_

Map an index aware IO action, over an array in parallel, while discarding the result.

Zipping

zip :: (Source r1 ix e1, Source r2 ix e2) => Array r1 ix e1 -> Array r2 ix e2 -> Array D ix (e1, e2) Source #

Zip two arrays

zip3 :: (Source r1 ix e1, Source r2 ix e2, Source r3 ix e3) => Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix (e1, e2, e3) Source #

Zip three arrays

unzip :: Source r ix (e1, e2) => Array r ix (e1, e2) -> (Array D ix e1, Array D ix e2) Source #

Unzip two arrays

unzip3 :: Source r ix (e1, e2, e3) => Array r ix (e1, e2, e3) -> (Array D ix e1, Array D ix e2, Array D ix e3) Source #

Unzip three arrays

zipWith :: (Source r1 ix e1, Source r2 ix e2) => (e1 -> e2 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array D ix e Source #

Zip two arrays with a function. Resulting array will be an intersection of source arrays in case their dimensions do not match.

zipWith3 :: (Source r1 ix e1, Source r2 ix e2, Source r3 ix e3) => (e1 -> e2 -> e3 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix e Source #

Just like zipWith, except zip three arrays with a function.

izipWith :: (Source r1 ix e1, Source r2 ix e2) => (ix -> e1 -> e2 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array D ix e Source #

Just like zipWith, except with an index aware function.

izipWith3 :: (Source r1 ix e1, Source r2 ix e2, Source r3 ix e3) => (ix -> e1 -> e2 -> e3 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix e Source #

Just like zipWith3, except with an index aware function.

liftArray2 :: (Source r1 ix a, Source r2 ix b) => (a -> b -> e) -> Array r1 ix a -> Array r2 ix b -> Array D ix e Source #

Similar to zipWith, except dimensions of both arrays either have to be the same, or at least one of the two array must be a singleton array, in which case it will behave as a map.

Since: 0.1.4

Folding

All folding is done in a row-major order.

Unstructured folds

Functions in this section will fold any Source array with respect to the inner Computation strategy setting.

fold Source #

Arguments

:: Source r ix e 
=> (e -> e -> e)

Folding function (like with left fold, first argument is an accumulator)

-> e

Initial element. Has to be neutral with respect to the folding function.

-> Array r ix e

Source array

-> e 

O(n) - Unstructured fold of an array.

ifoldMono Source #

Arguments

:: (Source r ix e, Monoid m) 
=> (ix -> e -> m)

Convert each element of an array to an appropriate Monoid.

-> Array r ix e

Source array

-> m 

O(n) - Monoidal fold over an array with an index aware function. Also known as reduce.

Since: 0.2.4

foldMono Source #

Arguments

:: (Source r ix e, Monoid m) 
=> (e -> m)

Convert each element of an array to an appropriate Monoid.

-> Array r ix e

Source array

-> m 

O(n) - Monoidal fold over an array. Also known as reduce.

Since: 0.1.4

ifoldSemi Source #

Arguments

:: (Source r ix e, Semigroup m) 
=> (ix -> e -> m)

Convert each element of an array to an appropriate Semigroup.

-> m

Initial element that must be neutral to the (<>) function.

-> Array r ix e

Source array

-> m 

O(n) - Semigroup fold over an array with an index aware function.

Since: 0.2.4

foldSemi Source #

Arguments

:: (Source r ix e, Semigroup m) 
=> (e -> m)

Convert each element of an array to an appropriate Semigroup.

-> m

Initial element that must be neutral to the (<>) function.

-> Array r ix e

Source array

-> m 

O(n) - Semigroup fold over an array.

Since: 0.1.6

minimum :: (Source r ix e, Ord e) => Array r ix e -> e Source #

O(n) - Compute minimum of all elements.

maximum :: (Source r ix e, Ord e) => Array r ix e -> e Source #

O(n) - Compute maximum of all elements.

sum :: (Source r ix e, Num e) => Array r ix e -> e Source #

O(n) - Compute sum of all elements.

product :: (Source r ix e, Num e) => Array r ix e -> e Source #

O(n) - Compute product of all elements.

and :: Source r ix Bool => Array r ix Bool -> Bool Source #

O(n) - Compute conjunction of all elements.

or :: Source r ix Bool => Array r ix Bool -> Bool Source #

O(n) - Compute disjunction of all elements.

all :: Source r ix e => (e -> Bool) -> Array r ix e -> Bool Source #

O(n) - Determines whether all element of the array satisfy the predicate.

any :: Source r ix e => (e -> Bool) -> Array r ix e -> Bool Source #

O(n) - Determines whether any element of the array satisfies the predicate.

Single dimension folds

Safe inner most

ifoldlInner :: (Index (Lower ix), Source r ix e) => (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Left fold over the inner most dimension with index aware function.

Since: 0.2.4

foldlInner :: (Index (Lower ix), Source r ix e) => (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Left fold over the inner most dimension.

Since: 0.2.4

ifoldrInner :: (Index (Lower ix), Source r ix e) => (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Right fold over the inner most dimension with index aware function.

Since: 0.2.4

foldrInner :: (Index (Lower ix), Source r ix e) => (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Right fold over the inner most dimension.

Since: 0.2.4

Type safe

ifoldlWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r ix e) => Dimension n -> (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Left fold along a specified dimension with an index aware function.

Since: 0.2.4

foldlWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r ix e) => Dimension n -> (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Left fold along a specified dimension.

Example

Expand
>>> let arr = makeArrayR U Seq (2 :. 5) (toLinearIndex (2 :. 5))
>>> arr
(Array U Seq (2 :. 5)
  [ [ 0,1,2,3,4 ]
  , [ 5,6,7,8,9 ]
  ])
>>> foldlWithin Dim1 (flip (:)) [] arr
(Array D Seq (2)
  [ [4,3,2,1,0],[9,8,7,6,5] ])
>>> foldlWithin Dim2 (flip (:)) [] arr
(Array D Seq (5)
  [ [5,0],[6,1],[7,2],[8,3],[9,4] ])

Since: 0.2.4

ifoldrWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r ix e) => Dimension n -> (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Right fold along a specified dimension with an index aware function.

Since: 0.2.4

foldrWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r ix e) => Dimension n -> (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Right fold along a specified dimension.

Since: 0.2.4

Partial

ifoldlWithin' :: (Index (Lower ix), Source r ix e) => Dim -> (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Similar to ifoldlWithin, except that dimension is specified at a value level, which means it will throw an exception on an invalid dimension.

Since: 0.2.4

foldlWithin' :: (Index (Lower ix), Source r ix e) => Dim -> (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Similar to foldlWithin, except that dimension is specified at a value level, which means it will throw an exception on an invalid dimension.

Since: 0.2.4

ifoldrWithin' :: (Index (Lower ix), Source r ix e) => Dim -> (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Similar to ifoldrWithin, except that dimension is specified at a value level, which means it will throw an exception on an invalid dimension.

Since: 0.2.4

foldrWithin' :: (Index (Lower ix), Source r ix e) => Dim -> (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #

Similar to foldrWithin, except that dimension is specified at a value level, which means it will throw an exception on an invalid dimension.

Since: 0.2.4

Sequential folds

Functions in this section will fold any Source array sequentially, regardless of the inner Computation strategy setting.

foldlS :: Source r ix e => (a -> e -> a) -> a -> Array r ix e -> a Source #

O(n) - Left fold, computed sequentially.

foldrS :: Source r ix e => (e -> a -> a) -> a -> Array r ix e -> a Source #

O(n) - Right fold, computed sequentially.

ifoldlS :: Source r ix e => (a -> ix -> e -> a) -> a -> Array r ix e -> a Source #

O(n) - Left fold with an index aware function, computed sequentially.

ifoldrS :: Source r ix e => (ix -> e -> a -> a) -> a -> Array r ix e -> a Source #

O(n) - Right fold with an index aware function, computed sequentially.

Monadic

foldlM :: (Source r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m a Source #

O(n) - Monadic left fold.

foldrM :: (Source r ix e, Monad m) => (e -> a -> m a) -> a -> Array r ix e -> m a Source #

O(n) - Monadic right fold.

foldlM_ :: (Source r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m () Source #

O(n) - Monadic left fold, that discards the result.

foldrM_ :: (Source r ix e, Monad m) => (e -> a -> m a) -> a -> Array r ix e -> m () Source #

O(n) - Monadic right fold, that discards the result.

ifoldlM :: (Source r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m a Source #

O(n) - Monadic left fold with an index aware function.

ifoldrM :: (Source r ix e, Monad m) => (ix -> e -> a -> m a) -> a -> Array r ix e -> m a Source #

O(n) - Monadic right fold with an index aware function.

ifoldlM_ :: (Source r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m () Source #

O(n) - Monadic left fold with an index aware function, that discards the result.

ifoldrM_ :: (Source r ix e, Monad m) => (ix -> e -> a -> m a) -> a -> Array r ix e -> m () Source #

O(n) - Monadic right fold with an index aware function, that discards the result.

Special folds

foldrFB :: Source r ix e => (e -> b -> b) -> b -> Array r ix e -> b Source #

Version of foldr that supports foldr/build list fusion implemented by GHC.

lazyFoldlS :: Source r ix e => (a -> e -> a) -> a -> Array r ix e -> a Source #

O(n) - Left fold, computed sequentially with lazy accumulator.

lazyFoldrS :: Source r ix e => (e -> a -> a) -> a -> Array r ix e -> a Source #

O(n) - Right fold, computed sequentially with lazy accumulator.

Parallel folds

Note It is important to compile with -threaded -with-rtsopts=-N flags, otherwise there will be no parallelization.

Functions in this section will fold any Source array in parallel, regardless of the inner Computation strategy setting. All of the parallel structured folds are performed inside IO monad, because referential transparency can't generally be preserved and results will depend on the number of cores/capabilities that computation is being performed on.

In contrast to sequential folds, each parallel folding function accepts two functions and two initial elements as arguments. This is necessary because an array is first split into chunks, which folded individually on separate cores with the first function, and the results of those folds are further folded with the second function.

foldlP Source #

Arguments

:: Source r ix e 
=> (a -> e -> a)

Folding function g.

-> a

Accumulator. Will be applied to g multiple times, thus must be neutral.

-> (b -> a -> b)

Chunk results folding function f.

-> b

Accumulator for results of chunks folding.

-> Array r ix e 
-> IO b 

O(n) - Left fold, computed in parallel. Parallelization of folding is implemented in such a way that an array is split into a number of chunks of equal length, plus an extra one for the left over. Number of chunks is the same as number of available cores (capabilities) plus one, and each chunk is individually folded by a separate core with a function g. Results from folding each chunk are further folded with another function f, thus allowing us to use information about the structure of an array during folding.

Examples

Expand
>>> foldlP (flip (:)) [] (flip (:)) [] $ makeArrayR U Seq (Ix1 11) id
[[10,9,8,7,6,5,4,3,2,1,0]]

And this is how the result would look like if the above computation would be performed in a program executed with +RTS -N3, i.e. with 3 capabilities:

>>> foldlOnP [1,2,3] (flip (:)) [] (flip (:)) [] $ makeArrayR U Seq (Ix1 11) id
[[10,9],[8,7,6],[5,4,3],[2,1,0]]

foldrP :: Source r ix e => (e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> IO b Source #

O(n) - Right fold, computed in parallel. Same as foldlP, except directed from the last element in the array towards beginning.

Examples

Expand
>>> foldrP (++) [] (:) [] $ makeArray2D (3,4) id
[(0,0),(0,1),(0,2),(0,3),(1,0),(1,1),(1,2),(1,3),(2,0),(2,1),(2,2),(2,3)]

ifoldlP :: Source r ix e => (a -> ix -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> IO b Source #

O(n) - Left fold with an index aware function, computed in parallel. Just like foldlP, except that folding function will receive an index of an element it is being applied to.

ifoldrP :: Source r ix e => (ix -> e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> IO b Source #

Just like ifoldrOnP, but allows you to specify which cores to run computation on.

foldlOnP :: Source r ix e => [Int] -> (a -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> IO b Source #

Just like foldlP, but allows you to specify which cores (capabilities) to run computation on. The order in which chunked results will be supplied to function f is guaranteed to be consecutive and aligned with the folding direction.

ifoldlIO Source #

Arguments

:: Source r ix e 
=> [Int]

List of capabilities

-> (a -> ix -> e -> IO a)

Index aware folding IO action

-> a

Accumulator

-> (b -> a -> IO b)

Folding action that is applied to results of parallel fold

-> b

Accumulator for chunks folding

-> Array r ix e 
-> IO b 

Parallel left fold.

foldrOnP :: Source r ix e => [Int] -> (e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> IO b Source #

Just like foldrP, but allows you to specify which cores to run computation on.

Examples

Expand

Number of wokers dictate the result structure:

>>> foldrOnP [1,2,3] (:) [] (:) [] $ makeArray1D 9 id
[[0,1,2],[3,4,5],[6,7,8]]
>>> foldrOnP [1,2,3] (:) [] (:) [] $ makeArray1D 10 id
[[0,1,2],[3,4,5],[6,7,8],[9]]
>>> foldrOnP [1,2,3] (:) [] (:) [] $ makeArray1D 12 id
[[0,1,2,3],[4,5,6,7],[8,9,10,11]]

But most of the time that structure is of no importance:

>>> foldrOnP [1,2,3] (++) [] (:) [] $ makeArray1D 10 id
[0,1,2,3,4,5,6,7,8,9]

Same as foldlOnP, order is guaranteed to be consecutive and in proper direction:

>>> fmap snd $ foldrOnP [1,2,3] (\x (i, acc) -> (i + 1, (i, x):acc)) (1, []) (:) [] $ makeArray1D 11 id
[(4,[0,1,2]),(3,[3,4,5]),(2,[6,7,8]),(1,[9,10])]
>>> fmap (P.zip [4,3..]) <$> foldrOnP [1,2,3] (:) [] (:) [] $ makeArray1D 11 id
[(4,[0,1,2]),(3,[3,4,5]),(2,[6,7,8]),(1,[9,10])]

ifoldlOnP :: Source r ix e => [Int] -> (a -> ix -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> IO b Source #

Just like ifoldlP, but allows you to specify which cores to run computation on.

ifoldrOnP :: Source r ix e => [Int] -> (ix -> e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> IO b Source #

O(n) - Right fold with an index aware function, computed in parallel. Same as ifoldlP, except directed from the last element in the array towards beginning.

ifoldrIO :: Source r ix e => [Int] -> (ix -> e -> a -> IO a) -> a -> (a -> b -> IO b) -> b -> Array r ix e -> IO b Source #

Parallel right fold. Differs from ifoldrP in that it accepts IO actions instead of the usual pure functions as arguments.

Transforming

Transpose

transpose :: Source r Ix2 e => Array r Ix2 e -> Array D Ix2 e Source #

Transpose a 2-dimensional array

Examples

Expand
>>> let arr = makeArrayR U Seq (2 :. 3) (toLinearIndex (2 :. 3))
>>> arr
(ArrayU Seq (2 :. 3)
  [ [ 0,1,2 ]
  , [ 3,4,5 ]
  ])
>>> transpose arr
(Array D Seq (3 :. 2)
  [ [ 0,3 ]
  , [ 1,4 ]
  , [ 2,5 ]
  ])

transposeInner :: (Index (Lower ix), Source r' ix e) => Array r' ix e -> Array D ix e Source #

Transpose inner two dimensions of at least rank-2 array.

Examples

Expand
>>> let arr = makeArrayR U Seq (2 :> 3 :. 4) fromIx3
>>> arr
(Array U Seq (2 :> 3 :. 4)
  [ [ [ (0,0,0),(0,0,1),(0,0,2),(0,0,3) ]
    , [ (0,1,0),(0,1,1),(0,1,2),(0,1,3) ]
    , [ (0,2,0),(0,2,1),(0,2,2),(0,2,3) ]
    ]
  , [ [ (1,0,0),(1,0,1),(1,0,2),(1,0,3) ]
    , [ (1,1,0),(1,1,1),(1,1,2),(1,1,3) ]
    , [ (1,2,0),(1,2,1),(1,2,2),(1,2,3) ]
    ]
  ])
>>> transposeInner arr
(Array D Seq (3 :> 2 :. 4)
  [ [ [ (0,0,0),(0,0,1),(0,0,2),(0,0,3) ]
    , [ (1,0,0),(1,0,1),(1,0,2),(1,0,3) ]
    ]
  , [ [ (0,1,0),(0,1,1),(0,1,2),(0,1,3) ]
    , [ (1,1,0),(1,1,1),(1,1,2),(1,1,3) ]
    ]
  , [ [ (0,2,0),(0,2,1),(0,2,2),(0,2,3) ]
    , [ (1,2,0),(1,2,1),(1,2,2),(1,2,3) ]
    ]
  ])

transposeOuter :: (Index (Lower ix), Source r' ix e) => Array r' ix e -> Array D ix e Source #

Transpose outer two dimensions of at least rank-2 array.

Examples

Expand
>>> let arr = makeArrayR U Seq (2 :> 3 :. 4) fromIx3
>>> arr
(Array U Seq (2 :> 3 :. 4)
  [ [ [ (0,0,0),(0,0,1),(0,0,2),(0,0,3) ]
    , [ (0,1,0),(0,1,1),(0,1,2),(0,1,3) ]
    , [ (0,2,0),(0,2,1),(0,2,2),(0,2,3) ]
    ]
  , [ [ (1,0,0),(1,0,1),(1,0,2),(1,0,3) ]
    , [ (1,1,0),(1,1,1),(1,1,2),(1,1,3) ]
    , [ (1,2,0),(1,2,1),(1,2,2),(1,2,3) ]
    ]
  ])
>>> transposeOuter arr
(Array D Seq (2 :> 4 :. 3)
  [ [ [ (0,0,0),(0,1,0),(0,2,0) ]
    , [ (0,0,1),(0,1,1),(0,2,1) ]
    , [ (0,0,2),(0,1,2),(0,2,2) ]
    , [ (0,0,3),(0,1,3),(0,2,3) ]
    ]
  , [ [ (1,0,0),(1,1,0),(1,2,0) ]
    , [ (1,0,1),(1,1,1),(1,2,1) ]
    , [ (1,0,2),(1,1,2),(1,2,2) ]
    , [ (1,0,3),(1,1,3),(1,2,3) ]
    ]
  ])

Backpermute

backpermute Source #

Arguments

:: (Source r' ix' e, Index ix) 
=> Sz ix

Size of the result array

-> (ix -> ix')

A function that maps indices of the new array into the source one.

-> Array r' ix' e

Source array.

-> Array D ix e 

Rearrange elements of an array into a new one.

Examples

Expand
>>> let arr = makeArrayR U Seq (2 :> 3 :. 4) fromIx3
>>> arr
(Array U Seq (2 :> 3 :. 4)
  [ [ [ (0,0,0),(0,0,1),(0,0,2),(0,0,3) ]
    , [ (0,1,0),(0,1,1),(0,1,2),(0,1,3) ]
    , [ (0,2,0),(0,2,1),(0,2,2),(0,2,3) ]
    ]
  , [ [ (1,0,0),(1,0,1),(1,0,2),(1,0,3) ]
    , [ (1,1,0),(1,1,1),(1,1,2),(1,1,3) ]
    , [ (1,2,0),(1,2,1),(1,2,2),(1,2,3) ]
    ]
  ])
>>> backpermute (4 :. 3) (\(i :. j) -> 0 :> j :. i) arr
(Array D Seq (4 :. 3)
  [ [ (0,0,0),(0,1,0),(0,2,0) ]
  , [ (0,0,1),(0,1,1),(0,2,1) ]
  , [ (0,0,2),(0,1,2),(0,2,2) ]
  , [ (0,0,3),(0,1,3),(0,2,3) ]
  ])

Resize

resize :: (Index ix', Size r ix e) => Sz ix' -> Array r ix e -> Maybe (Array r ix' e) Source #

O(1) - Changes the shape of an array. Returns Nothing if total number of elements does not match the source array.

resize' :: (Index ix', Size r ix e) => Sz ix' -> Array r ix e -> Array r ix' e Source #

Same as resize, but will throw an error if supplied dimensions are incorrect.

Extract

extract Source #

Arguments

:: Size r ix e 
=> ix

Starting index

-> Sz ix

Size of the resulting array

-> Array r ix e

Source array

-> Maybe (Array (EltRepr r ix) ix e) 

Extract a sub-array from within a larger source array. Array that is being extracted must be fully encapsulated in a source array, otherwise Nothing is returned,

extract' Source #

Arguments

:: Size r ix e 
=> ix

Starting index

-> Sz ix

Size of the resulting array

-> Array r ix e

Source array

-> Array (EltRepr r ix) ix e 

Same as extract, but will throw an error if supplied dimensions are incorrect.

extractFromTo Source #

Arguments

:: Size r ix e 
=> ix

Starting index

-> ix

Index up to which elmenets should be extracted.

-> Array r ix e

Source array.

-> Maybe (Array (EltRepr r ix) ix e) 

Similar to extract, except it takes starting and ending index. Result array will not include the ending index.

extractFromTo' Source #

Arguments

:: Size r ix e 
=> ix

Starting index

-> ix

Index up to which elmenets should be extracted.

-> Array r ix e

Source array.

-> Array (EltRepr r ix) ix e 

Same as extractFromTo, but throws an error on invalid indices.

Since: 0.2.4

Append/Split

append :: (Source r1 ix e, Source r2 ix e) => Dim -> Array r1 ix e -> Array r2 ix e -> Maybe (Array D ix e) Source #

Append two arrays together along a particular dimension. Sizes of both arrays must match, with an allowed exception of the dimension they are being appended along, otherwise Nothing is returned.

Examples

Expand

Append two 2D arrays along both dimensions. Note that they have the same shape.

>>> let arrA = makeArrayR U Seq (2 :. 3) (\(i :. j) -> ('A', i, j))
>>> let arrB = makeArrayR U Seq (2 :. 3) (\(i :. j) -> ('B', i, j))
>>> append 1 arrA arrB
Just (Array D Seq (2 :. 6)
  [ [ ('A',0,0),('A',0,1),('A',0,2),('B',0,0),('B',0,1),('B',0,2) ]
  , [ ('A',1,0),('A',1,1),('A',1,2),('B',1,0),('B',1,1),('B',1,2) ]
  ])
>>> append 2 arrA arrB
Just (Array D Seq (4 :. 3)
  [ [ ('A',0,0),('A',0,1),('A',0,2) ]
  , [ ('A',1,0),('A',1,1),('A',1,2) ]
  , [ ('B',0,0),('B',0,1),('B',0,2) ]
  , [ ('B',1,0),('B',1,1),('B',1,2) ]
  ])

Now appending arrays with different sizes:

>>> let arrC = makeArrayR U Seq (2 :. 4) (\(i :. j) -> ('C', i, j))
>>> append 1 arrA arrC
Just (Array D Seq (2 :. 7)
  [ [ ('A',0,0),('A',0,1),('A',0,2),('C',0,0),('C',0,1),('C',0,2),('C',0,3) ]
  , [ ('A',1,0),('A',1,1),('A',1,2),('C',1,0),('C',1,1),('C',1,2),('C',1,3) ]
  ])
>>> append 2 arrA arrC
Nothing

append' :: (Source r1 ix e, Source r2 ix e) => Dim -> Array r1 ix e -> Array r2 ix e -> Array D ix e Source #

Same as append, but will throw an error instead of returning Nothing on mismatched sizes.

splitAt Source #

Arguments

:: (Size r ix e, r' ~ EltRepr r ix) 
=> Dim

Dimension along which to split

-> Int

Index along the dimension to split at

-> Array r ix e

Source array

-> Maybe (Array r' ix e, Array r' ix e) 

O(1) - Split an array at an index along a specified dimension.

splitAt' :: (Size r ix e, r' ~ EltRepr r ix) => Dim -> Int -> Array r ix e -> (Array r' ix e, Array r' ix e) Source #

Same as splitAt, but will throw an error instead of returning Nothing on wrong dimension and index out of bounds.

Traverse

traverse Source #

Arguments

:: (Source r1 ix1 e1, Index ix) 
=> Sz ix

Size of the result array

-> ((ix1 -> e1) -> ix -> e)

Function that will receive a source array safe index function and an index for an element it should return a value of.

-> Array r1 ix1 e1

Source array

-> Array D ix e 

Create an array by traversing a source array.

traverse2 :: (Source r1 ix1 e1, Source r2 ix2 e2, Index ix) => Sz ix -> ((ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e Source #

Create an array by traversing two source arrays.

Slicing

From the outside

(!>) :: OuterSlice r ix e => Array r ix e -> Int -> Elt r ix e infixl 4 Source #

O(1) - Slices the array from the outside. For 2-dimensional array this will be equivalent of taking a row. Throws an error when index is out of bounds.

Examples

Expand

You could say that slicing from outside is synonymous to slicing from the end or slicing at the highermost dimension. For example with rank-3 arrays outer slice would be equivalent to getting a page:

>>> let arr = makeArrayR U Seq (3 :> 2 :. 4) fromIx3
>>> arr
(Array U Seq (3 :> 2 :. 4)
  [ [ [ (0,0,0),(0,0,1),(0,0,2),(0,0,3) ]
    , [ (0,1,0),(0,1,1),(0,1,2),(0,1,3) ]
    ]
  , [ [ (1,0,0),(1,0,1),(1,0,2),(1,0,3) ]
    , [ (1,1,0),(1,1,1),(1,1,2),(1,1,3) ]
    ]
  , [ [ (2,0,0),(2,0,1),(2,0,2),(2,0,3) ]
    , [ (2,1,0),(2,1,1),(2,1,2),(2,1,3) ]
    ]
  ])
>>> arr !> 2
(Array M Seq (2 :. 4)
  [ [ (2,0,0),(2,0,1),(2,0,2),(2,0,3) ]
  , [ (2,1,0),(2,1,1),(2,1,2),(2,1,3) ]
  ])

There is nothing wrong with chaining, mixing and matching slicing operators, or even using them to index arrays:

>>> arr !> 2 !> 0 !> 3
(2,0,3)
>>> arr !> 2 <! 3 ! 0
(2,0,3)
>>> arr !> 2 !> 0 !> 3 == arr ! 2 :> 0 :. 3
True

(!?>) :: OuterSlice r ix e => Array r ix e -> Int -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Just like !> slices the array from the outside, but returns Nothing when index is out of bounds.

(??>) :: OuterSlice r ix e => Maybe (Array r ix e) -> Int -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Safe slicing continuation from the outside. Similarly to (!>) slices the array from the outside, but takes Maybe array as input and returns Nothing when index is out of bounds.

Examples

Expand
>>> let arr = makeArrayR U Seq (3 :> 2 :. 4) fromIx3
>>> arr !?> 2 ??> 0 ??> 3
Just (2,0,3)
>>> arr !?> 2 ??> 0 ??> -1
Nothing
>>> arr !?> -2 ??> 0 ?? 1
Nothing

From the inside

(<!) :: InnerSlice r ix e => Array r ix e -> Int -> Elt r ix e infixl 4 Source #

O(1) - Similarly to (!>) slice an array from an opposite direction.

(<!?) :: InnerSlice r ix e => Array r ix e -> Int -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Safe slice from the inside

(<??) :: InnerSlice r ix e => Maybe (Array r ix e) -> Int -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Safe slicing continuation from the inside

From within

(<!>) :: Slice r ix e => Array r ix e -> (Dim, Int) -> Elt r ix e infixl 4 Source #

O(1) - Slices the array in any available dimension. Throws an error when index is out of bounds or dimensions is invalid.

arr !> i == arr <!> (dimensions (size arr), i)
arr <! i == arr <!> (1,i)

(<!?>) :: Slice r ix e => Array r ix e -> (Dim, Int) -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Same as (<!>), but fails gracefully with a Nothing, instead of an error

(<??>) :: Slice r ix e => Maybe (Array r ix e) -> (Dim, Int) -> Maybe (Elt r ix e) infixl 4 Source #

O(1) - Safe slicing continuation from within.

Conversion

List

fromList Source #

Arguments

:: (Nested LN Ix1 e, Nested L Ix1 e, Ragged L Ix1 e, Mutable r Ix1 e) 
=> Comp

Computation startegy to use

-> [e]

Flat list

-> Array r Ix1 e 

Convert a flat list into a vector

fromLists :: (Nested LN ix e, Nested L ix e, Ragged L ix e, Mutable r ix e) => Comp -> [ListItem ix e] -> Maybe (Array r ix e) Source #

O(n) - Convert a nested list into an array. Nested list must be of a rectangular shape, otherwise a runtime error will occur. Also, nestedness must match the rank of resulting array, which should be specified through an explicit type signature.

Examples

Expand
>>> fromLists Seq [[1,2],[3,4]] :: Maybe (Array U Ix2 Int)
Just (Array U Seq (2 :. 2)
  [ [ 1,2 ]
  , [ 3,4 ]
  ])
>>> fromLists Par [[[1,2,3]],[[4,5,6]]] :: Maybe (Array U Ix3 Int)
Just (Array U Par (2 :> 1 :. 3)
  [ [ [ 1,2,3 ]
    ]
  , [ [ 4,5,6 ]
    ]
  ])

Elements of a boxed array could be lists themselves if necessary, but cannot be ragged:

>>> fromLists Seq [[[1,2,3]],[[4,5]]] :: Maybe (Array B Ix2 [Int])
Just (Array B Seq (2 :. 1)
  [ [ [1,2,3] ]
  , [ [4,5] ]
  ])
>>> fromLists Seq [[[1,2,3]],[[4,5]]] :: Maybe (Array B Ix3 Int)
Nothing

fromLists' Source #

Arguments

:: (Nested LN ix e, Nested L ix e, Ragged L ix e, Mutable r ix e) 
=> Comp

Computation startegy to use

-> [ListItem ix e]

Nested list

-> Array r ix e 

Same as fromLists, but will throw an error on irregular shaped lists.

Note: This function is the same as if you would turn on {-# LANGUAGE OverloadedLists #-} extension. For that reason you can also use fromList.

fromLists' Seq xs == fromList xs

Examples

Expand

Convert a list of lists into a 2D Array

>>> fromLists' Seq [[1,2],[3,4]] :: Array U Ix2 Int
(Array U Seq (2 :. 2)
  [ [ 1,2 ]
  , [ 3,4 ]
  ])

Above example implemented using GHC's OverloadedLists extension:

>>> :set -XOverloadedLists
>>> [[1,2],[3,4]] :: Array U Ix2 Int
(Array U Seq (2 :. 2)
  [ [ 1,2 ]
  , [ 3,4 ]
  ])

Example of failure on conversion of an irregular nested list.

>>> fromLists' Seq [[1],[3,4]] :: Array U Ix2 Int
(Array U *** Exception: Too many elements in a row

toList :: Source r ix e => Array r ix e -> [e] Source #

Convert any array to a flat list.

Examples

Expand
>>> toList $ makeArrayR U Seq (2 :. 3) fromIx2
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]

toLists :: (Nested LN ix e, Nested L ix e, Construct L ix e, Source r ix e) => Array r ix e -> [ListItem ix e] Source #

O(n) - Convert an array into a nested list. Array rank and list nestedness will always match, but you can use toList, toLists2, etc. if flattening of inner dimensions is desired.

Note: This function is almost the same as toList.

Examples

Expand
>>> let arr = makeArrayR U Seq (2 :> 1 :. 3) fromIx3
>>> print arr
(Array U Seq (2 :> 1 :. 3)
  [ [ [ (0,0,0),(0,0,1),(0,0,2) ]
    ]
  , [ [ (1,0,0),(1,0,1),(1,0,2) ]
    ]
  ])
>>> toLists arr
[[[(0,0,0),(0,0,1),(0,0,2)]],[[(1,0,0),(1,0,1),(1,0,2)]]]

toLists2 :: (Source r ix e, Index (Lower ix)) => Array r ix e -> [[e]] Source #

Convert an array with at least 2 dimensions into a list of lists. Inner dimensions will get flattened.

Examples

Expand
>>> toList2 $ makeArrayR U Seq (2 :. 3) fromIx2
[[(0,0),(0,1),(0,2)],[(1,0),(1,1),(1,2)]]
>>> toList2 $ makeArrayR U Seq (2 :> 1 :. 3) fromIx3
[[(0,0,0),(0,0,1),(0,0,2)],[(1,0,0),(1,0,1),(1,0,2)]]

toLists3 :: (Index (Lower (Lower ix)), Index (Lower ix), Source r ix e) => Array r ix e -> [[[e]]] Source #

Convert an array with at least 3 dimensions into a 3 deep nested list. Inner dimensions will get flattened.

toLists4 :: (Index (Lower (Lower (Lower ix))), Index (Lower (Lower ix)), Index (Lower ix), Source r ix e) => Array r ix e -> [[[[e]]]] Source #

Convert an array with at least 4 dimensions into a 4 deep nested list. Inner dimensions will get flattened.

Mutable

Core

Representations

Stencil

Numeric Operations