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

Copyright(c) Alexey Kuleshevich 2018-2019
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 representations describe classic arrays and are backed by a contiguous chunk of memory reserved for the elements (or pointers to 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.

There are also array representations that only describe how values for its elements can be computed or loaded into memory, as such, they are represented by functions and do not impose the memory overhead, that is normally associated with arrays. They are needed for proper fusion and parallelization of computation.

  • D - delayed array that is a mere function from an index to an element. Also known as Pull array. Crucial representation for fusing computation. Use computeAs in order to load array into Manifest representation.
  • DL - delayed load array representation that describes how an array can be loaded. Also known as Push array. Useful for fusing various array combining functions. Use computeAs in order to load array into Manifest representation.
  • DS - delayed stream vector representation that describes how to handle a vector with possibility of unknown length. Useful for filtering and unfolding. Use computeAs in order to load such vector into Manifest representation.
  • DI - delayed interleaved array. Same as D, but performs better with unbalanced computation, when evaluation of one element takes much longer than of its 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 a perfect intermediary for lists <-> 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

With constant value

empty :: forall r ix e. Construct r ix e => Array r ix e Source #

Create an Array with no elements. By itself it is not particularly useful, but it serves as a nice base for constructing larger arrays.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> :set -XTypeApplications
>>> xs = empty @DL @Ix1 @Double
>>> snoc (cons 4 (cons 5 xs)) 22
Array DL Seq (Sz1 3)
  [ 4.0, 5.0, 22.0 ]

Since: 0.3.0

singleton Source #

Arguments

:: Construct r ix e 
=> e

The only element

-> Array r ix e 

Create an Array with a single element.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> singleton 7 :: Array D Ix4 Double
Array D Seq (Sz (1 :> 1 :> 1 :. 1))
  [ [ [ [ 7.0 ]
      ]
    ]
  ]

Instead of specifying type signature we could use TypeApplications

>>> :set -XTypeApplications
>>> singleton @U @Ix4 @Double 7
Array U Seq (Sz (1 :> 1 :> 1 :. 1))
  [ [ [ [ 7.0 ]
      ]
    ]
  ]

Since: 0.1.0

replicate :: forall r ix e. Construct r ix e => Comp -> Sz ix -> e -> Array r ix e Source #

Replicate the same element

Since: 0.3.0

With 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.

-> (ix -> e)

Function to generate elements at a particular index

-> Array r ix e 

Construct an Array. Resulting type either has to be unambiguously inferred or restricted manually, like in the example below. Use "Data.Massiv.Array.makeArrayR" if you'd like to specify representation as an argument.

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

Instead of restricting the full type manually we can use TypeApplications as convenience:

>>> :set -XTypeApplications
>>> makeArray @P @_ @Double Seq (Sz2 3 4) $ \(i :. j) -> logBase (fromIntegral i) (fromIntegral j)
Array P Seq (Sz (3 :. 4))
  [ [ NaN, -0.0, -0.0, -0.0 ]
  , [ -Infinity, NaN, Infinity, Infinity ]
  , [ -Infinity, 0.0, 1.0, 1.5849625007211563 ]
  ]

Since: 0.1.0

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

Same as makeArray, but produce elements using linear row-major index.

>>> import Data.Massiv.Array
>>> makeArrayLinear Seq (Sz (2 :. 4)) id :: Array D Ix2 Int
Array D Seq (Sz (2 :. 4))
  [ [ 0, 1, 2, 3 ]
  , [ 4, 5, 6, 7 ]
  ]

Since: 0.3.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.

Examples

Expand
>>> import Data.Massiv.Array
>>> makeArrayR U Par (Sz (2 :> 3 :. 4)) (\ (i :> j :. k) -> i * i + j * j == k * k)
Array U Par (Sz (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 ]
    ]
  ]

Since: 0.1.0

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

Same as makeArrayLinear, but with ability to supply resulting representation

Since: 0.3.0

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

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

Since: 0.1.0

Iterating

iterateN :: forall ix e. Index ix => Sz ix -> (e -> e) -> e -> Array DL ix e Source #

Sequentially iterate over each cell in the array in the row-major order while continuously aplying the accumulator at each step.

Example

Expand
>>> import Data.Massiv.Array
>>> iterateN (Sz2 2 10) succ (10 :: Int)
Array DL Seq (Sz (2 :. 10))
  [ [ 11, 12, 13, 14, 15, 16, 17, 18, 19, 20 ]
  , [ 21, 22, 23, 24, 25, 26, 27, 28, 29, 30 ]
  ]

Since: 0.3.0

iiterateN :: forall ix e. Index ix => Sz ix -> (e -> ix -> e) -> e -> Array DL ix e Source #

Same as iterateN, but with index aware function.

Since: 0.3.0

Unfolding

unfoldr :: (s -> Maybe (e, s)) -> s -> Array DS Ix1 e Source #

Right unfolding function. Useful when we do not have any idea ahead of time on how many elements the vector will have.

Example

Expand
>>> import Data.Massiv.Array as A
>>> unfoldr (\i -> if i < 9 then Just (i*i, i + 1) else Nothing) (0 :: Int)
Array DS Seq (Sz1 9)
  [ 0, 1, 4, 9, 16, 25, 36, 49, 64 ]
>>> unfoldr (\i -> if sqrt i < 3 then Just (i * i, i + 1) else Nothing) (0 :: Double)
Array DS Seq (Sz1 9)
  [ 0.0, 1.0, 4.0, 9.0, 16.0, 25.0, 36.0, 49.0, 64.0 ]

Since: 0.4.1

unfoldrN Source #

Arguments

:: Sz1

Maximum number of elements that the vector can have

-> (s -> Maybe (e, s))

Unfolding function. Stops when Nothing is reaturned or maximum number of elements is reached.

-> s

Inititial element.

-> Array DS Ix1 e 

Right unfolding function with limited number of elements.

Example

Expand
>>> import Data.Massiv.Array as A
>>> unfoldrN 9 (\i -> Just (i*i, i + 1)) (0 :: Int)
Array DS Seq (Sz1 9)
  [ 0, 1, 4, 9, 16, 25, 36, 49, 64 ]

Since: 0.4.1

unfoldlS_ :: Construct DL ix e => Sz ix -> (a -> (a, e)) -> a -> Array DL ix e Source #

Unfold sequentially from the end. There is no way to save the accumulator after unfolding is done, since resulting array is delayed, but it's possible to use unfoldlPrimM to achive such effect.

Since: 0.3.0

iunfoldlS_ :: Construct DL ix e => Sz ix -> (ix -> a -> (a, e)) -> a -> Array DL ix e Source #

Unfold sequentially from the right with an index aware function.

Since: 0.3.0

unfoldrS_ :: forall ix e a. Construct DL ix e => Sz ix -> (a -> (e, a)) -> a -> Array DL ix e Source #

Right unfold of a delayed load array. For the inverse direction use unfoldlS_.

Examples

Expand
>>> import Data.Massiv.Array
>>> unfoldrS_ (Sz1 10) (\xs -> (head xs, tail xs)) ([10 ..] :: [Int])
Array DL Seq (Sz1 10)
  [ 10, 11, 12, 13, 14, 15, 16, 17, 18, 19 ]

Since: 0.3.0

iunfoldrS_ :: Construct DL ix e => Sz ix -> (a -> ix -> (e, a)) -> a -> Array DL ix e Source #

Right unfold of a delayed load array with index aware function

Since: 0.3.0

Random

randomArray Source #

Arguments

:: Index ix 
=> g

Initial random value generator

-> (g -> (g, g))

A function that can split a generator in two independent generators

-> (g -> (e, g))

A function that produces a random value and the next generator

-> Comp

Computation strategy.

-> Sz ix

Resulting size of the array.

-> Array DL ix e 

Create an array with random values by using a pure splittable random number generator such as one provided by either splitmix or random packages. If you don't have a splittable generator consider using randomArrayS or randomArrayIO instead.

Because of the pure nature of the generator and its splitability we are not only able to parallelize the random value generation, but also guarantee that it will be deterministic, granted none of the arguments have changed.

Examples

Expand
>>> import Data.Massiv.Array
>>> import System.Random.SplitMix as SplitMix
>>> gen = SplitMix.mkSMGen 217
>>> randomArray gen SplitMix.splitSMGen SplitMix.nextDouble (ParN 2) (Sz2 2 3) :: Array DL Ix2 Double
Array DL (ParN 2) (Sz (2 :. 3))
  [ [ 0.7383156058619669, 0.39904053166835896, 0.5617584038393628 ]
  , [ 0.7218718218678238, 0.7006722805067258, 0.7225894731396042 ]
  ]
>>> import Data.Massiv.Array
>>> import System.Random as System
>>> gen = System.mkStdGen 217
>>> randomArray gen System.split System.random (ParN 2) (Sz2 2 3) :: Array DL Ix2 Double
Array DL (ParN 2) (Sz (2 :. 3))
  [ [ 0.15191527341922206, 0.2045537167404079, 0.9635356052820256 ]
  , [ 9.308278528094238e-2, 0.7200934018606843, 0.23173694193083583 ]
  ]

Since: 0.3.3

randomArrayS Source #

Arguments

:: Mutable r ix e 
=> g

Initial random value generator

-> Sz ix

Resulting size of the array.

-> (g -> (e, g))

A function that produces a random value and the next generator

-> (g, Array r ix e) 

Similar to randomArray but performs generation sequentially, which means it doesn't require splitability property. Another consequence is that it returns the new generator together with manifest array of random values.

Examples

Expand
>>> import Data.Massiv.Array
>>> import System.Random.SplitMix as SplitMix
>>> gen = SplitMix.mkSMGen 217
>>> snd $ randomArrayS gen (Sz2 2 3) SplitMix.nextDouble :: Array P Ix2 Double
Array P Seq (Sz (2 :. 3))
  [ [ 0.8878273949359751, 0.11290807610140963, 0.7383156058619669 ]
  , [ 0.39904053166835896, 0.5617584038393628, 0.16248374266020216 ]
  ]
>>> import Data.Massiv.Array
>>> import System.Random.Mersenne.Pure64 as MT
>>> gen = MT.pureMT 217
>>> snd $ randomArrayS gen (Sz2 2 3) MT.randomDouble :: Array P Ix2 Double
Array P Seq (Sz (2 :. 3))
  [ [ 0.5504018416543631, 0.22504666452851707, 0.4480480867867128 ]
  , [ 0.7139711572975297, 0.49401087853770953, 0.9397201599368645 ]
  ]
>>> import Data.Massiv.Array
>>> import System.Random as System
>>> gen = System.mkStdGen 217
>>> snd $ randomArrayS gen (Sz2 2 3) System.random :: Array P Ix2 Double
Array P Seq (Sz (2 :. 3))
  [ [ 0.7972230393466304, 0.4485860543300083, 0.257773196880671 ]
  , [ 0.19115043859955794, 0.33784788936970034, 3.479381605706322e-2 ]
  ]

Since: 0.3.4

randomArrayWS Source #

Arguments

:: (Mutable r ix e, MonadUnliftIO m, PrimMonad m) 
=> WorkerStates g

Use initWorkerStates to initialize you per thread generators

-> Sz ix

Resulting size of the array

-> (g -> m e)

Generate the value using the per thread generator.

-> m (Array r ix e) 

This is a stateful approach of generating random values. If your generator is pure and splittable, it is better to use randomArray instead, which will give you a pure, deterministic and parallelizable generation of arrays. On the other hand, if your generator is not thread safe, which is most likely the case, instead of using some sort of global mutex, WorkerStates allows you to keep track of individual state per worker (thread), which fits parallelization of random value generation perfectly. All that needs to be done is generators need to be initialized once per worker and then they can be reused as many times as necessary.

Examples

Expand

In the example below we take a stateful random generator from wmc-random, which is not thread safe, and safely parallelize it by giving each thread it's own generator:

λ> import Data.Massiv.Array
λ> import System.Random.MWC (createSystemRandom, uniformR)
λ> import System.Random.MWC.Distributions (standard)
λ> gens <- initWorkerStates Par (\_ -> createSystemRandom)
λ> randomArrayWS gens (Sz2 2 3) standard :: IO (Array P Ix2 Double)
Array P Par (Sz (2 :. 3))
  [ [ -0.9066144845415213, 0.5264323240310042, -1.320943607597422 ]
  , [ -0.6837929005619592, -0.3041255565826211, 6.53353089112833e-2 ]
  ]
λ> randomArrayWS gens (Sz1 10) (uniformR (0, 9)) :: IO (Array P Ix1 Int)
Array P Par (Sz1 10)
  [ 3, 6, 1, 2, 1, 7, 6, 0, 8, 8 ]

Since: 0.3.4

Applicative

makeArrayA :: forall r ix e f. (Mutable r ix e, Applicative f) => Sz ix -> (ix -> f e) -> f (Array r ix e) Source #

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

Note - using generateArray or generateArrayS will always be faster, althought not always possible.

Since: 0.2.6

makeArrayAR :: forall r ix e f. (Mutable r ix e, Applicative f) => r -> Sz ix -> (ix -> f e) -> f (Array r ix e) Source #

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

Since: 0.2.6

Enumeration

(...) :: Index ix => ix -> ix -> Array D ix ix infix 4 Source #

Handy synonym for rangeInclusive Seq

>>> Ix1 4 ... 10
Array D Seq (Sz1 7)
  [ 4, 5, 6, 7, 8, 9, 10 ]

Since: 0.3.0

(..:) :: Index ix => ix -> ix -> Array D ix ix infix 4 Source #

Handy synonym for range Seq

>>> Ix1 4 ..: 10
Array D Seq (Sz1 6)
  [ 4, 5, 6, 7, 8, 9 ]

Since: 0.3.0

range :: Index ix => Comp -> ix -> ix -> Array D ix ix Source #

Create an array of indices with a range from start to finish (not-including), where indices are incremeted by one.

Examples

Expand
>>> import Data.Massiv.Array
>>> range Seq (Ix1 1) 6
Array D Seq (Sz1 5)
  [ 1, 2, 3, 4, 5 ]
>>> fromIx2 <$> range Seq (-1) (2 :. 2)
Array D Seq (Sz (3 :. 3))
  [ [ (-1,-1), (-1,0), (-1,1) ]
  , [ (0,-1), (0,0), (0,1) ]
  , [ (1,-1), (1,0), (1,1) ]
  ]

Since: 0.1.0

rangeStepM Source #

Arguments

:: (Index ix, MonadThrow m) 
=> Comp

Computation strategy

-> ix

Start

-> ix

Step (Can't have zeros)

-> ix

End

-> m (Array D ix ix) 

Same as range, but with a custom step.

Examples

Expand
>>> import Data.Massiv.Array
>>> rangeStepM Seq (Ix1 1) 2 8
Array D Seq (Sz1 4)
  [ 1, 3, 5, 7 ]
>>> rangeStepM Seq (Ix1 1) 0 8
*** Exception: IndexZeroException: 0

Since: 0.3.0

rangeStep' :: Index ix => Comp -> ix -> ix -> ix -> Array D ix ix Source #

Same as rangeStepM, but will throw an error whenever step contains zeros.

Example

Expand
>>> import Data.Massiv.Array
>>> rangeStep' Seq (Ix1 1) 2 6
Array D Seq (Sz1 3)
  [ 1, 3, 5 ]

Since: 0.3.0

rangeInclusive :: Index ix => Comp -> ix -> ix -> Array D ix ix Source #

Just like range, except the finish index is included.

Since: 0.3.0

rangeStepInclusiveM :: (MonadThrow m, Index ix) => Comp -> ix -> ix -> ix -> m (Array D ix ix) Source #

Just like rangeStep, except the finish index is included.

Since: 0.3.0

rangeStepInclusive' :: Index ix => Comp -> ix -> ix -> ix -> Array D ix ix Source #

Just like range, except the finish index is included.

Since: 0.3.1

rangeSize Source #

Arguments

:: Index ix 
=> Comp 
-> ix

x - start value

-> Sz ix

sz - Size of resulting array

-> Array D ix ix 

Create an array of specified size with indices starting with some index at position 0 and incremented by 1 until the end of the array is reached

Since: 0.3.0

rangeStepSize Source #

Arguments

:: Index ix 
=> Comp 
-> ix

x - start value

-> ix

delta - step value

-> Sz ix

sz - Size of resulting array

-> Array D ix ix 

Same as rangeSize, but with ability to specify the step.

Since: 0.3.0

enumFromN Source #

Arguments

:: Num e 
=> Comp 
-> e

x - start value

-> Sz1

n - length of resulting vector.

-> Array D Ix1 e 

Same as enumFromStepN with step delta = 1.

Examples

Expand
>>> import Data.Massiv.Array
>>> enumFromN Seq (5 :: Double) 3
Array D Seq (Sz1 3)
  [ 5.0, 6.0, 7.0 ]

Since: 0.1.0

enumFromStepN Source #

Arguments

:: Num e 
=> Comp 
-> e

x - start value

-> e

delta - step value

-> Sz1

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.

Examples

Expand
>>> import Data.Massiv.Array
>>> enumFromStepN Seq 1 (0.1 :: Double) 5
Array D Seq (Sz1 5)
  [ 1.0, 1.1, 1.2, 1.3, 1.4 ]

Since: 0.1.0

Expansion

expandWithin :: forall ix e r n a. (IsIndexDimension ix n, Manifest r (Lower ix) a) => Dimension n -> Sz1 -> (a -> Ix1 -> e) -> Array r (Lower ix) a -> Array D ix e 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
>>> import Data.Massiv.Array
>>> a = makeArrayR U Seq (Sz1 6) (+10) -- Imagine (+10) is some expensive function
>>> a
Array U Seq (Sz1 6)
  [ 10, 11, 12, 13, 14, 15 ]
>>> expandWithin Dim1 5 (\ e j -> (j + 1) * 100 + e) a :: Array D Ix2 Int
Array D Seq (Sz (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 (Sz (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

expandWithinM :: (Index ix, Manifest r (Lower ix) a, MonadThrow m) => Dim -> Sz1 -> (a -> Ix1 -> b) -> Array r (Lower ix) a -> m (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.4.0

expandWithin' :: (Index ix, Manifest r (Lower ix) a) => Dim -> Sz1 -> (a -> Ix1 -> 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) => Sz1 -> (a -> Ix1 -> 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) => Sz1 -> (a -> Ix1 -> 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 :: Load r ix e => Array r ix e -> Comp Source #

Get computation strategy of this array

Since: 0.1.0

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

Set computation strategy for this array

Example

Expand
>>> :set -XTypeApplications
>>> import Data.Massiv.Array
>>> a = singleton @DL @Ix1 @Int 0
>>> a
Array DL Seq (Sz1 1)
  [ 0 ]
>>> setComp (ParN 6) a -- use 6 capabilities
Array DL (ParN 6) (Sz1 1)
  [ 0 ]

compute :: forall r ix e r'. (Mutable r ix e, Load 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

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

computeAs :: (Mutable r ix e, Load 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
>>> import Data.Massiv.Array
>>> computeAs P $ range Seq (Ix1 0) 10
Array P Seq (Sz1 10)
  [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9 ]

computeProxy :: (Mutable r ix e, Load 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 only really for cases when representation constructor or TypeApplications extension aren't desireable for some reason:

>>> import Data.Proxy
>>> import Data.Massiv.Array
>>> computeProxy (Proxy :: Proxy P) $ (^ (2 :: Int)) <$> range Seq (Ix1 0) 10
Array P Seq (Sz1 10)
  [ 0, 1, 4, 9, 16, 25, 36, 49, 64, 81 ]

Since: 0.1.1

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

This is just like convert, but restricted to Source arrays. Will be a noop if resulting type is the same as the input.

Since: 0.1.0

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

Same as compute, but with Stride.

O(n div k) - Where n is numer of elements in the source array and k is number of elemts in the stride.

Since: 0.3.0

computeWithStrideAs :: (Mutable r ix e, StrideLoad 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.

Since: 0.3.0

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

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

Since: 0.1.0

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

O(n) - conversion between array types. A full copy will occur, unless when the source and result arrays are of the same representation, in which case it is an O(1) operation.

Since: 0.1.0

convertAs :: (Mutable r ix e, Load 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.

Since: 0.1.0

convertProxy :: (Mutable r ix e, Load 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

fromRaggedArrayM :: forall r ix e r' m. (Mutable r ix e, Ragged r' ix e, Load r' ix e, MonadThrow m) => Array r' ix e -> m (Array r ix e) Source #

Convert a ragged array into a common array with rectangular shape. Throws ShapeException whenever supplied ragged array does not have a rectangular shape.

Since: 0.4.0

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

Same as fromRaggedArrayM, but will throw a pure exception if its shape is not rectangular.

Since: 0.1.1

Size

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

Get the size of an immutabe array

Since: 0.1.0

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

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

Examples

Expand
>>> import Data.Massiv.Array
>>> elemsCount $ range Seq (Ix1 10) 15
5

Since: 0.1.0

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

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

Examples

Expand
>>> import Data.Massiv.Array
>>> isEmpty $ range Seq (Ix2 10 20) (11 :. 21)
False
>>> isEmpty $ range Seq (Ix2 10 20) (10 :. 21)
True

Since: 0.1.0

Indexing

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

Infix version of indexM.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> :set -XTypeApplications
>>> a <- fromListsM @U @Ix2 @Int Seq [[1,2,3],[4,5,6]]
>>> a
Array U Seq (Sz (2 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  ]
>>> a !? 0 :. 2
3
>>> a !? 0 :. 3
*** Exception: IndexOutOfBoundsException: (0 :. 3) is not safe for (Sz (2 :. 3))
>>> a !? 0 :. 3 :: Maybe Int
Nothing

Since: 0.1.0

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

Infix version of index'.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> a = computeAs U $ iterateN (Sz (2 :. 3)) succ (0 :: Int)
>>> a
Array U Seq (Sz (2 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  ]
>>> a ! 0 :. 2
3
>>> a ! 0 :. 3
*** Exception: IndexOutOfBoundsException: (0 :. 3) is not safe for (Sz (2 :. 3))

Since: 0.1.0

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

O(1) - Lookup an element in the array, where array itself is wrapped with MonadThrow. This operator is useful when used together with slicing or other functions that can fail.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> :set -XTypeApplications
>>> ma = fromListsM @U @Ix3 @Int @Maybe Seq [[[1,2,3]],[[4,5,6]]]
>>> ma
Just (Array U Seq (Sz (2 :> 1 :. 3))
  [ [ [ 1, 2, 3 ]
    ]
  , [ [ 4, 5, 6 ]
    ]
  ]
)
>>> ma ??> 1
Just (Array M Seq (Sz (1 :. 3))
  [ [ 4, 5, 6 ]
  ]
)
>>> ma ??> 1 ?? 0 :. 2
Just 6
>>> ma ?? 1 :> 0 :. 2
Just 6

Since: 0.1.0

indexM :: (Manifest r ix e, MonadThrow m) => Array r ix e -> ix -> m e Source #

O(1) - Lookup an element in the array. Throws IndexOutOfBoundsException, when index is out of bounds and returns the element at the supplied index otherwise.

Since: 0.3.0

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 and returns the element at the supplied index otherwise. Use indexM instead, since it is more generaland can just as well be used with Maybe.

Since: 0.1.0

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

O(1) - Lookup an element in the array. This is a partial function and it can throw IndexOutOfBoundsException inside pure code. It is safer to use index instead.

Examples

Expand
>>> import Data.Massiv.Array
>>> :set -XOverloadedLists
>>> xs = [0..100] :: Array U Ix1 Int
>>> index' xs 50
50
>>> index' xs 150
*** Exception: IndexOutOfBoundsException: 150 is not safe for (Sz1 101)

Since: 0.1.0

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.

Examples

Expand
>>> import Data.Massiv.Array
>>> :set -XOverloadedLists
>>> xs = [0..100] :: Array P Ix1 Int
>>> defaultIndex 999 xs 100
100
>>> defaultIndex 999 xs 101
999

Since: 0.1.0

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.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> :set -XOverloadedLists
>>> xs = [0..100] :: Array U Ix1 Int
>>> borderIndex Wrap xs <$> range Seq 99 104
Array D Seq (Sz1 5)
  [ 99, 100, 0, 1, 2 ]

Since: 0.1.0

evaluateM :: (Source r ix e, MonadThrow m) => Array r ix e -> ix -> m e Source #

This is just like indexM 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.

Examples

Expand
>>> import Control.Exception
>>> import Data.Massiv.Array
>>> evaluateM (range Seq (Ix2 10 20) (100 :. 210)) 50 :: Either SomeException Ix2
Right (60 :. 70)
>>> evaluateM (range Seq (Ix2 10 20) (100 :. 210)) 150 :: Either SomeException Ix2
Left (IndexOutOfBoundsException: (150 :. 150) is not safe for (Sz (90 :. 190)))

Since: 0.3.0

evaluate' :: Source r ix e => Array r ix e -> ix -> e Source #

Similar to evaluateM, but will throw an exception in pure code.

Examples

Expand
>>> import Data.Massiv.Array
>>> evaluate' (range Seq (Ix2 10 20) (100 :. 210)) 50
60 :. 70
>>> evaluate' (range Seq (Ix2 10 20) (100 :. 210)) 150
*** Exception: IndexOutOfBoundsException: (150 :. 150) is not safe for (Sz (90 :. 190))

Since: 0.3.0

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

Applicative

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

Traverse with an Applicative action over an array sequentially.

Note - using traversePrim will always be faster, althought not always possible.

Since: 0.2.6

traverseA_ :: forall r ix e a f. (Source r ix e, Applicative f) => (e -> f a) -> Array r ix e -> f () Source #

Traverse sequentially over a source array, while discarding the result.

Since: 0.3.0

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

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

Since: 0.2.6

itraverseA_ :: forall r ix e a f. (Source r ix a, Applicative f) => (ix -> a -> f e) -> Array r ix a -> f () 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 #

Deprecated: In favor of traverseA

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 #

Deprecated: In favor of itraverseA

Same as itraverseA, except with ability to specify representation.

Since: 0.2.6

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

Sequence actions in a source array.

Since: 0.3.0

sequenceA_ :: forall r ix e f. (Source r ix (f e), Applicative f) => Array r ix (f e) -> f () Source #

Sequence actions in a source array, while discarding the result.

Since: 0.3.0

PrimMonad

traversePrim :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, PrimMonad m) => (a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Traverse sequentially within PrimMonad over an array with an action.

Since: 0.3.0

itraversePrim :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, PrimMonad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as traversePrim, but traverse with index aware action.

Since: 0.3.0

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

Deprecated: In favor of traversePrim

Same as traversePrim, but with ability to specify the desired representation.

Since: 0.3.0

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

Deprecated: In favor of itraversePrim

Same as itraversePrim, but with ability to specify the desired representation.

Since: 0.3.0

Monadic mapping

Sequential

mapM Source #

Arguments

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

Mapping action

-> Array r' ix a

Source array

-> m (Array r ix b) 

Map a monadic action over an array sequentially.

Since: 0.2.6

mapMR :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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 :: forall r ix b r' a m. (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
>>> import Data.Massiv.Array as A
>>> rangeStepM Par (Ix1 10) 12 60 >>= A.mapM_ print
10
22
34
46
58

Since: 0.1.0

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:

>>> import Data.Massiv.Array as A
>>> import Data.IORef
>>> ref <- newIORef 0 :: IO (IORef Int)
>>> A.forM_ (range Seq (Ix1 0) 1000) $ \ i -> modifyIORef' ref (+i)
>>> readIORef ref
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
>>> import Data.Massiv.Array
>>> imapM_ (curry print) $ range Seq (Ix1 10) 15
(0,10)
(1,11)
(2,12)
(3,13)
(4,14)

Since: 0.1.0

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 :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => (a -> m b) -> Array r' ix a -> m (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

mapWS :: forall r ix b r' a s m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> (a -> s -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as imapWS, but without the index.

Since: 0.3.4

mapIO_ :: (Source r b e, MonadUnliftIO m) => (e -> m a) -> Array r b e -> m () 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 :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as mapIO but map an index aware action instead.

Since: 0.2.6

imapWS :: forall r ix b r' a s m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> (ix -> a -> s -> m b) -> Array r' ix a -> m (Array r ix b) Source #

Same as imapIO, but ignores the inner computation strategy and uses stateful workers during computation instead. Use initWorkerStates for the WorkerStates initialization.

Since: 0.3.4

imapIO_ :: (Source r ix e, MonadUnliftIO m) => (ix -> e -> m a) -> Array r ix e -> m () Source #

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

Since: 0.2.6

forIO :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => Array r' ix a -> (a -> m b) -> m (Array r ix b) Source #

Same as mapIO but with arguments flipped.

Since: 0.2.6

forWS :: forall r ix b r' a s m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Array r' ix a -> (a -> s -> m b) -> m (Array r ix b) Source #

Same as iforWS, but without the index.

Since: 0.3.4

forIO_ :: (Source r ix e, MonadUnliftIO m) => Array r ix e -> (e -> m a) -> m () Source #

Same as mapIO_ but with arguments flipped.

Example

Expand

This is the same example as in forM_, with important difference that accumulator ref will be modified concurrently by as many threads as there are capabilities.

>>> import Data.Massiv.Array
>>> import Data.IORef
>>> ref <- newIORef 0 :: IO (IORef Int)
>>> forIO_ (range Par (Ix1 0) 1000) $ \ i -> atomicModifyIORef' ref (\v -> (v+i, ()))
>>> readIORef ref
499500

Since: 0.2.6

iforIO :: forall r ix b r' a m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => Array r' ix a -> (ix -> a -> m b) -> m (Array r ix b) Source #

Same as imapIO but with arguments flipped.

Since: 0.2.6

iforWS :: forall r ix b r' a s m. (Source r' ix a, Mutable r ix b, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Array r' ix a -> (ix -> a -> s -> m b) -> m (Array r ix b) Source #

Same as imapWS, but with source array and mapping action arguments flipped.

Since: 0.3.4

iforIO_ :: (Source r ix a, MonadUnliftIO m) => Array r ix a -> (ix -> a -> m b) -> m () Source #

Same as imapIO_ but with arguments flipped.

Since: 0.2.6

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

Same as imapM_, but will use the supplied scheduler.

Since: 0.3.1

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

Same as imapM_, but will use the supplied scheduler.

Since: 0.3.1

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

Applicative

zipWithA :: (Source r1 ix e1, Source r2 ix e2, Applicative f, Mutable r ix e) => (e1 -> e2 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> f (Array r ix e) Source #

Similar to zipWith, except does it sequentiall and using the Applicative. Note that resulting array has Mutable representation.

Since: 0.3.0

izipWithA :: (Source r1 ix e1, Source r2 ix e2, Applicative f, Mutable r ix e) => (ix -> e1 -> e2 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> f (Array r ix e) Source #

Similar to zipWith, except does it sequentiall and using the Applicative. Note that resulting array has Mutable representation.

Since: 0.3.0

zipWith3A :: (Source r1 ix e1, Source r2 ix e2, Source r3 ix e3, Applicative f, Mutable r ix e) => (e1 -> e2 -> e3 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> f (Array r ix e) Source #

Same as zipWithA, but for three arrays.

Since: 0.3.0

izipWith3A :: (Source r1 ix e1, Source r2 ix e2, Source r3 ix e3, Applicative f, Mutable r ix e) => (ix -> e1 -> e2 -> e3 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> f (Array r ix e) Source #

Same as izipWithA, but for three arrays.

Since: 0.3.0

Filtering

Maybe

mapMaybeS :: Stream r ix a => (a -> Maybe b) -> Array r ix a -> Array DS Ix1 b Source #

Apply a function to each element of the array, while discarding Nothing and keepingt he Maybe result.

Since: 0.4.1

imapMaybeS :: Source r ix a => (ix -> a -> Maybe b) -> Array r ix a -> Array DS Ix1 b Source #

Similar to mapMaybeM, but map with an index aware function.

Since: 0.4.1

mapMaybeM :: (Stream r ix a, Applicative f) => (a -> f (Maybe b)) -> Array r ix a -> f (Array DS Ix1 b) Source #

Similar to mapMaybeS, but with the use of Applicative

Since: 0.4.1

imapMaybeM :: (Source r ix a, Applicative f) => (ix -> a -> f (Maybe b)) -> Array r ix a -> f (Array DS Ix1 b) Source #

Similar to mapMaybeM, but map with an index aware function.

Since: 0.4.1

Predicate

filterS :: Stream r ix e => (e -> Bool) -> Array r ix e -> Array DS Ix1 e Source #

Sequentially filter out elements from the array according to the supplied predicate.

Example

Expand
>>> import Data.Massiv.Array as A
>>> arr = makeArrayR D Seq (Sz2 3 4) fromIx2
>>> arr
Array D Seq (Sz (3 :. 4))
  [ [ (0,0), (0,1), (0,2), (0,3) ]
  , [ (1,0), (1,1), (1,2), (1,3) ]
  , [ (2,0), (2,1), (2,2), (2,3) ]
  ]
>>> filterS (even . fst) arr
Array DS Seq (Sz1 8)
  [ (0,0), (0,1), (0,2), (0,3), (2,0), (2,1), (2,2), (2,3) ]

Since: 0.4.1

ifilterS :: Source r ix a => (ix -> a -> Bool) -> Array r ix a -> Array DS Ix1 a Source #

Similar to filterS, but map with an index aware function.

Since: 0.4.1

filterM :: (Stream r ix e, Applicative f) => (e -> f Bool) -> Array r ix e -> f (Array DS Ix1 e) Source #

Sequentially filter out elements from the array according to the supplied applicative predicate.

Example

Expand
>>> import Data.Massiv.Array as A
>>> arr = makeArrayR D Seq (Sz2 3 4) fromIx2
>>> arr
Array D Seq (Sz (3 :. 4))
  [ [ (0,0), (0,1), (0,2), (0,3) ]
  , [ (1,0), (1,1), (1,2), (1,3) ]
  , [ (2,0), (2,1), (2,2), (2,3) ]
  ]
>>> filterM (Just . odd . fst) arr
Just (Array DS Seq (Sz1 4)
  [ (1,0), (1,1), (1,2), (1,3) ]
)
>>> filterM (\ix@(_, j) -> print ix >> return (even j)) arr
(0,0)
(0,1)
(0,2)
(0,3)
(1,0)
(1,1)
(1,2)
(1,3)
(2,0)
(2,1)
(2,2)
(2,3)
Array DS Seq (Sz1 6)
  [ (0,0), (0,2), (1,0), (1,2), (2,0), (2,2) ]

Since: 0.4.1

ifilterM :: (Source r ix a, Applicative f) => (ix -> a -> f Bool) -> Array r ix a -> f (Array DS Ix1 a) Source #

Similar to filterM, but map with an index aware function.

Since: 0.4.1

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

:: (Monoid e, Source r ix e) 
=> Array r ix e

Source array

-> e 

O(n) - Unstructured fold of an array.

Since: 0.3.0

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) - This is exactly like foldMap, but for arrays. Fold over an array, while converting each element into a Monoid. Also known as map-reduce. If elements of the array are already a Monoid you can use fold instead.

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

minimumM :: (MonadThrow m, Source r ix e, Ord e) => Array r ix e -> m e Source #

O(n) - Compute minimum of all elements.

Since: 0.3.0

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

O(n) - Compute minimum of all elements.

Since: 0.3.0

maximumM :: (MonadThrow m, Source r ix e, Ord e) => Array r ix e -> m e Source #

O(n) - Compute maximum of all elements.

Since: 0.3.0

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

O(n) - Compute maximum of all elements.

Since: 0.3.0

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

O(n) - Compute sum of all elements.

Since: 0.1.0

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

O(n) - Compute product of all elements.

Since: 0.1.0

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

O(n) - Compute conjunction of all elements.

Since: 0.1.0

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

O(n) - Compute disjunction of all elements.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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
>>> import Data.Massiv.Array
>>> :set -XTypeApplications
>>> arr = makeArrayLinear @U Seq (Sz (2 :. 5)) id
>>> arr
Array U Seq (Sz (2 :. 5))
  [ [ 0, 1, 2, 3, 4 ]
  , [ 5, 6, 7, 8, 9 ]
  ]
>>> foldlWithin Dim1 (flip (:)) [] arr
Array D Seq (Sz1 2)
  [ [4,3,2,1,0], [9,8,7,6,5] ]
>>> foldlWithin Dim2 (flip (:)) [] arr
Array D Seq (Sz1 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.

Since: 0.1.0

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

O(n) - Right fold, computed sequentially.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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

O(n) - Monadic right fold.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

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

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

Since: 0.1.0

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

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

Since: 0.1.0

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

:: (MonadIO m, 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 
-> m b 

O(n) - Left fold, computed with respect of array's computation strategy. Because we do potentially split the folding among many threads, we also need a combining function and an accumulator for the results. Depending on the number of threads being used, results can be different, hence is the MonadIO constraint.

Examples

Expand
>>> import Data.Massiv.Array
>>> foldlP (flip (:)) [] (flip (:)) [] $ makeArrayR D Seq (Sz1 6) id
[[5,4,3,2,1,0]]
>>> foldlP (flip (:)) [] (++) [] $ makeArrayR D Seq (Sz1 6) id
[5,4,3,2,1,0]
>>> foldlP (flip (:)) [] (flip (:)) [] $ makeArrayR D (ParN 3) (Sz1 6) id
[[5,4],[3,2],[1,0]]
>>> foldlP (flip (:)) [] (++) [] $ makeArrayR D (ParN 3) (Sz1 6) id
[1,0,3,2,5,4]

Since: 0.1.0

foldrP :: (MonadIO m, Source r ix e) => (e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> m b Source #

O(n) - Right fold, computed with respect to computation strategy. Same as foldlP, except directed from the last element in the array towards beginning.

Examples

Expand
>>> import Data.Massiv.Array
>>> foldrP (:) [] (++) [] $ makeArrayR D (ParN 2) (Sz2 2 3) fromIx2
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]
>>> foldrP (:) [] (:) [] $ makeArrayR D Seq (Sz1 6) id
[[0,1,2,3,4,5]]
>>> foldrP (:) [] (:) [] $ makeArrayR D (ParN 3) (Sz1 6) id
[[0,1],[2,3],[4,5]]

Since: 0.1.0

ifoldlP :: (MonadIO m, Source r ix e) => (a -> ix -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> m 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.

Since: 0.1.0

ifoldrP :: (MonadIO m, Source r ix e) => (ix -> e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> m b Source #

O(n) - Right fold with an index aware function, while respecting the computation strategy. Same as ifoldlP, except directed from the last element in the array towards beginning, but also row-major.

Since: 0.1.0

ifoldlIO Source #

Arguments

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

Index aware folding IO action

-> a

Accumulator

-> (b -> a -> m b)

Folding action that is applied to the results of a parallel fold

-> b

Accumulator for chunks folding

-> Array r ix e 
-> m b 

Similar to ifoldlP, except that folding functions themselves do live in IO

Since: 0.1.0

ifoldrIO :: (MonadUnliftIO m, Source r ix e) => (ix -> e -> a -> m a) -> a -> (a -> b -> m b) -> b -> Array r ix e -> m b Source #

Similar to ifoldrP, except that folding functions themselves do live in IO

Since: 0.1.0

Transforming

Transpose

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

Transpose a 2-dimensional array

Examples

Expand
>>> import Data.Massiv.Array
>>> arr = makeArrayLinearR D Seq (Sz (2 :. 3)) id
>>> arr
Array D Seq (Sz (2 :. 3))
  [ [ 0, 1, 2 ]
  , [ 3, 4, 5 ]
  ]
>>> transpose arr
Array D Seq (Sz (3 :. 2))
  [ [ 0, 3 ]
  , [ 1, 4 ]
  , [ 2, 5 ]
  ]

Since: 0.1.0

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
>>> import Data.Massiv.Array
>>> arr = makeArrayLinearR U Seq (Sz (2 :> 3 :. 4)) id
>>> arr
Array U Seq (Sz (2 :> 3 :. 4))
  [ [ [ 0, 1, 2, 3 ]
    , [ 4, 5, 6, 7 ]
    , [ 8, 9, 10, 11 ]
    ]
  , [ [ 12, 13, 14, 15 ]
    , [ 16, 17, 18, 19 ]
    , [ 20, 21, 22, 23 ]
    ]
  ]
>>> transposeInner arr
Array D Seq (Sz (3 :> 2 :. 4))
  [ [ [ 0, 1, 2, 3 ]
    , [ 12, 13, 14, 15 ]
    ]
  , [ [ 4, 5, 6, 7 ]
    , [ 16, 17, 18, 19 ]
    ]
  , [ [ 8, 9, 10, 11 ]
    , [ 20, 21, 22, 23 ]
    ]
  ]

Since: 0.1.0

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
>>> import Data.Massiv.Array
>>> :set -XTypeApplications
>>> arr = makeArrayLinear @U Seq (Sz (2 :> 3 :. 4)) id
>>> arr
Array U Seq (Sz (2 :> 3 :. 4))
  [ [ [ 0, 1, 2, 3 ]
    , [ 4, 5, 6, 7 ]
    , [ 8, 9, 10, 11 ]
    ]
  , [ [ 12, 13, 14, 15 ]
    , [ 16, 17, 18, 19 ]
    , [ 20, 21, 22, 23 ]
    ]
  ]
>>> transposeOuter arr
Array D Seq (Sz (2 :> 4 :. 3))
  [ [ [ 0, 4, 8 ]
    , [ 1, 5, 9 ]
    , [ 2, 6, 10 ]
    , [ 3, 7, 11 ]
    ]
  , [ [ 12, 16, 20 ]
    , [ 13, 17, 21 ]
    , [ 14, 18, 22 ]
    , [ 15, 19, 23 ]
    ]
  ]

Since: 0.1.0

Reverse

reverse :: (IsIndexDimension ix n, Source r ix e) => Dimension n -> Array r ix e -> Array D ix e Source #

Reverse an array along some dimension. Dimension supplied is checked at compile time.

Example

Expand
>>> import Data.Massiv.Array as A
>>> arr = makeArrayLinear Seq (Sz2 4 5) (+10) :: Array D Ix2 Int
>>> arr
Array D Seq (Sz (4 :. 5))
  [ [ 10, 11, 12, 13, 14 ]
  , [ 15, 16, 17, 18, 19 ]
  , [ 20, 21, 22, 23, 24 ]
  , [ 25, 26, 27, 28, 29 ]
  ]
>>> A.reverse Dim1 arr
Array D Seq (Sz (4 :. 5))
  [ [ 14, 13, 12, 11, 10 ]
  , [ 19, 18, 17, 16, 15 ]
  , [ 24, 23, 22, 21, 20 ]
  , [ 29, 28, 27, 26, 25 ]
  ]
>>> A.reverse Dim2 arr
Array D Seq (Sz (4 :. 5))
  [ [ 25, 26, 27, 28, 29 ]
  , [ 20, 21, 22, 23, 24 ]
  , [ 15, 16, 17, 18, 19 ]
  , [ 10, 11, 12, 13, 14 ]
  ]

Since: 0.4.1

reverse' :: Source r ix e => Dim -> Array r ix e -> Array D ix e Source #

Reverse an array along some dimension. Same as reverseM, but throws the IndexDimensionException from pure code.

Since: 0.4.1

reverseM :: (MonadThrow m, Source r ix e) => Dim -> Array r ix e -> m (Array D ix e) Source #

Similarly to reverse, flip an array along a particular dimension, but throws IndexDimensionException for an incorrect dimension.

Since: 0.4.1

Backpermute

backpermuteM Source #

Arguments

:: (Mutable r ix e, Source r' ix' e, MonadUnliftIO m, PrimMonad m, MonadThrow m) 
=> 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.

-> m (Array r ix e) 

Rearrange elements of an array into a new one by using a function that maps indices of the newly created one into the old one. This function can throw IndexOutOfBoundsException.

Examples

Expand
>>> import Data.Massiv.Array
>>> :set -XTypeApplications
>>> arr = makeArrayLinear @D Seq (Sz (2 :> 3 :. 4)) id
>>> arr
Array D Seq (Sz (2 :> 3 :. 4))
  [ [ [ 0, 1, 2, 3 ]
    , [ 4, 5, 6, 7 ]
    , [ 8, 9, 10, 11 ]
    ]
  , [ [ 12, 13, 14, 15 ]
    , [ 16, 17, 18, 19 ]
    , [ 20, 21, 22, 23 ]
    ]
  ]
>>> backpermuteM @U (Sz (4 :. 2)) (\(i :. j) -> j :> j :. i) arr
Array U Seq (Sz (4 :. 2))
  [ [ 0, 16 ]
  , [ 1, 17 ]
  , [ 2, 18 ]
  , [ 3, 19 ]
  ]

Since: 0.3.0

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 

Similar to backpermuteM, with a few notable differences:

  • Creates a delayed array, instead of manifest, therefore it can be fused
  • Respects computation strategy, so it can be parallelized
  • Throws a runtime IndexOutOfBoundsException from pure code.

Since: 0.3.0

Resize

resizeM :: (MonadThrow m, Index ix', Load r ix e, Resize r ix) => Sz ix' -> Array r ix e -> m (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.

Since: 0.3.0

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

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

Since: 0.1.0

flatten :: (Load r ix e, Resize r ix) => Array r ix e -> Array r Ix1 e Source #

O(1) - Reduce a multi-dimensional array into a flat vector

Since: 0.3.1

Extract

extractM Source #

Arguments

:: (MonadThrow m, Extract r ix e) 
=> ix

Starting index

-> Sz ix

Size of the resulting array

-> Array r ix e

Source array

-> m (Array (R r) 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 SizeSubregionException will be thrown.

extract' Source #

Arguments

:: Extract r ix e 
=> ix

Starting index

-> Sz ix

Size of the resulting array

-> Array r ix e

Source array

-> Array (R r) ix e 

Same as extractM, but will throw a runtime exception from pure code if supplied dimensions are incorrect.

Since: 0.1.0

extractFromToM Source #

Arguments

:: (MonadThrow m, Extract r ix e) 
=> ix

Starting index

-> ix

Index up to which elements should be extracted.

-> Array r ix e

Source array.

-> m (Array (R r) ix e) 

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

Since: 0.3.0

extractFromTo' Source #

Arguments

:: Extract r ix e 
=> ix

Starting index

-> ix

Index up to which elmenets should be extracted.

-> Array r ix e

Source array.

-> Array (R r) ix e 

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

Since: 0.2.4

deleteRowsM :: (MonadThrow m, Extract r ix e, Source (R r) ix e, Index (Lower ix)) => Ix1 -> Sz Ix1 -> Array r ix e -> m (Array DL ix e) Source #

Similar to deleteRegionM, but drop a specified number of rows from an array that has at least 2 dimensions.

Example

Expand
>>> import Data.Massiv.Array
>>> arr = fromIx2 <$> (0 :. 0 ..: 3 :. 6)
>>> arr
Array D Seq (Sz (3 :. 6))
  [ [ (0,0), (0,1), (0,2), (0,3), (0,4), (0,5) ]
  , [ (1,0), (1,1), (1,2), (1,3), (1,4), (1,5) ]
  , [ (2,0), (2,1), (2,2), (2,3), (2,4), (2,5) ]
  ]
>>> deleteRowsM 1 1 arr
Array DL Seq (Sz (2 :. 6))
  [ [ (0,0), (0,1), (0,2), (0,3), (0,4), (0,5) ]
  , [ (2,0), (2,1), (2,2), (2,3), (2,4), (2,5) ]
  ]

Since: 0.3.5

deleteColumnsM :: (MonadThrow m, Extract r ix e, Source (R r) ix e) => Ix1 -> Sz Ix1 -> Array r ix e -> m (Array DL ix e) Source #

Similar to deleteRegionM, but drop a specified number of columns an array.

Example

Expand
>>> import Data.Massiv.Array
>>> arr = fromIx2 <$> (0 :. 0 ..: 3 :. 6)
>>> arr
Array D Seq (Sz (3 :. 6))
  [ [ (0,0), (0,1), (0,2), (0,3), (0,4), (0,5) ]
  , [ (1,0), (1,1), (1,2), (1,3), (1,4), (1,5) ]
  , [ (2,0), (2,1), (2,2), (2,3), (2,4), (2,5) ]
  ]
>>> deleteColumnsM 2 3 arr
Array DL Seq (Sz (3 :. 3))
  [ [ (0,0), (0,1), (0,5) ]
  , [ (1,0), (1,1), (1,5) ]
  , [ (2,0), (2,1), (2,5) ]
  ]

Since: 0.3.5

deleteRegionM Source #

Arguments

:: (MonadThrow m, Extract r ix e, Source (R r) ix e) 
=> Dim

Along which axis should the removal happen

-> Ix1

At which index to start dropping slices

-> Sz Ix1

Number of slices to drop

-> Array r ix e

Array that will have it's subarray removed

-> m (Array DL ix e) 

Delete a region from an array along the specified dimension.

Examples

Expand
>>> import Data.Massiv.Array
>>> arr = fromIx3 <$> (0 :> 0 :. 0 ..: 3 :> 2 :. 6)
>>> deleteRegionM 1 2 3 arr
Array DL Seq (Sz (3 :> 2 :. 3))
  [ [ [ (0,0,0), (0,0,1), (0,0,5) ]
    , [ (0,1,0), (0,1,1), (0,1,5) ]
    ]
  , [ [ (1,0,0), (1,0,1), (1,0,5) ]
    , [ (1,1,0), (1,1,1), (1,1,5) ]
    ]
  , [ [ (2,0,0), (2,0,1), (2,0,5) ]
    , [ (2,1,0), (2,1,1), (2,1,5) ]
    ]
  ]
>>> v = Ix1 0 ... 10
>>> deleteRegionM 1 3 5 v
Array DL Seq (Sz1 6)
  [ 0, 1, 2, 8, 9, 10 ]

Since: 0.3.5

Append/Split

cons :: e -> Array DL Ix1 e -> Array DL Ix1 e Source #

O(1) - Add an element to the vector from the left side

Since: 0.3.0

unconsM :: (MonadThrow m, Source r Ix1 e) => Array r Ix1 e -> m (e, Array D Ix1 e) Source #

O(1) - Take one element off the vector from the left side.

Since: 0.3.0

snoc :: Array DL Ix1 e -> e -> Array DL Ix1 e Source #

O(1) - Add an element to the vector from the right side

Since: 0.3.0

unsnocM :: (MonadThrow m, Source r Ix1 e) => Array r Ix1 e -> m (Array D Ix1 e, e) Source #

O(1) - Take one element off the vector from the right side.

Since: 0.3.0

appendM :: (MonadThrow m, Source r1 ix e, Source r2 ix e) => Dim -> Array r1 ix e -> Array r2 ix e -> m (Array DL 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 do agree on inner dimensions.

>>> import Data.Massiv.Array
>>> arrA = makeArrayR U Seq (Sz2 2 3) (\(i :. j) -> ('A', i, j))
>>> arrB = makeArrayR U Seq (Sz2 2 3) (\(i :. j) -> ('B', i, j))
>>> appendM 1 arrA arrB
Array DL Seq (Sz (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) ]
  ]
>>> appendM 2 arrA arrB
Array DL Seq (Sz (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:

>>> arrC = makeArrayR U Seq (Sz (2 :. 4)) (\(i :. j) -> ('C', i, j))
>>> appendM 1 arrA arrC
Array DL Seq (Sz (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) ]
  ]
>>> appendM 2 arrA arrC
*** Exception: SizeMismatchException: (Sz (2 :. 3)) vs (Sz (2 :. 4))

Since: 0.3.0

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

Same as appendM, but will throw an exception in pure code on mismatched sizes.

Since: 0.3.0

concatM :: (MonadThrow m, Foldable f, Source r ix e) => Dim -> f (Array r ix e) -> m (Array DL ix e) Source #

Concatenate many arrays together along some dimension. It is important that all sizes are equal, with an exception of the dimensions along which concatenation happens, otherwise it doues result in a SizeMismatchException exception.

Since: 0.3.0

concat' :: (Foldable f, Source r ix e) => Dim -> f (Array r ix e) -> Array DL ix e Source #

Concat many arrays together along some dimension.

Since: 0.3.0

splitAtM Source #

Arguments

:: (MonadThrow m, Extract r ix e) 
=> Dim

Dimension along which to split

-> Int

Index along the dimension to split at

-> Array r ix e

Source array

-> m (Array (R r) ix e, Array (R r) ix e) 

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

Since: 0.3.0

splitAt' :: Extract r ix e => Dim -> Int -> Array r ix e -> (Array (R r) ix e, Array (R r) ix e) Source #

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

Since: 0.1.0

splitExtractM Source #

Arguments

:: (MonadThrow m, Extract r ix e, Source (R r) ix e) 
=> Dim

Dimension along which to do the extraction

-> Ix1

Start index along the dimension that needs to be extracted

-> Sz Ix1

Size of the extracted array along the dimension that it will be extracted

-> Array r ix e 
-> m (Array (R r) ix e, Array (R r) ix e, Array (R r) ix e) 

Split an array in three parts across some dimension

Since: 0.3.5

takeS :: Stream r ix e => Sz1 -> Array r ix e -> Array DS Ix1 e Source #

Extract first n elements from the stream vector

Since: 0.4.1

dropS :: Stream r ix e => Sz1 -> Array r ix e -> Array DS Ix1 e Source #

Keep all but first n elements from the stream vector.

Since: 0.4.1

Upsample/Downsample

upsample :: Load r ix e => e -> Stride ix -> Array r ix e -> Array DL ix e Source #

Insert the same element into a Loadable array according to the stride.

Since: 0.3.0

downsample :: Source r ix e => Stride ix -> Array r ix e -> Array DL ix e Source #

Discard elements from the source array according to the stride.

Since: 0.3.0

Zoom

zoomWithGrid Source #

Arguments

:: Source r ix e 
=> e

Value to use for the grid

-> Stride ix

Scaling factor

-> Array r ix e

Source array

-> Array DL ix e 

Replicate each element of the array by a factor in stride along each dimension and surround each such group with a box of supplied grid value. It will essentially zoom up an array and create a grid around each element from the original array. Very useful for zooming up images to inspect individual pixels.

Example

Expand
>>> import Data.Massiv.Array as A
>>> zoomWithGrid 0 (Stride (2 :. 3)) $ resize' (Sz2 3 2) (Ix1 1 ... 6)
Array DL Seq (Sz (10 :. 9))
  [ [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 1, 1, 1, 0, 2, 2, 2, 0 ]
  , [ 0, 1, 1, 1, 0, 2, 2, 2, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 3, 3, 3, 0, 4, 4, 4, 0 ]
  , [ 0, 3, 3, 3, 0, 4, 4, 4, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 5, 5, 5, 0, 6, 6, 6, 0 ]
  , [ 0, 5, 5, 5, 0, 6, 6, 6, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  ]

Since: 0.3.1

Transform

transformM :: forall r ix e r' ix' e' a m. (Mutable r ix e, Source r' ix' e', MonadUnliftIO m, PrimMonad m, MonadThrow m) => (Sz ix' -> m (Sz ix, a)) -> (a -> (ix' -> m e') -> ix -> m e) -> Array r' ix' e' -> m (Array r ix e) Source #

General array transformation, that forces computation and produces a manifest array.

Since: 0.3.0

transform' :: (Source r' ix' e', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e Source #

General array transformation

Since: 0.3.0

transform2M :: (Mutable r ix e, Source r1 ix1 e1, Source r2 ix2 e2, MonadUnliftIO m, PrimMonad m, MonadThrow m) => (Sz ix1 -> Sz ix2 -> m (Sz ix, a)) -> (a -> (ix1 -> m e1) -> (ix2 -> m e2) -> ix -> m e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> m (Array r ix e) Source #

Same as transformM, but operates on two arrays

Since: 0.3.0

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

Same as transform', but operates on two arrays

Since: 0.3.0

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:

>>> import Data.Massiv.Array
>>> arr = makeArrayR U Seq (Sz (3 :> 2 :. 4)) fromIx3
>>> arr
Array U Seq (Sz (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 (Sz (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

Since: 0.1.0

(!?>) :: (MonadThrow m, OuterSlice r ix e) => Array r ix e -> Int -> m (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.

Since: 0.1.0

(??>) :: (MonadThrow m, OuterSlice r ix e) => m (Array r ix e) -> Int -> m (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
>>> import Data.Massiv.Array
>>> arr = makeArrayR U Seq (Sz (3 :> 2 :. 4)) fromIx3
>>> arr !?> 2 ??> 0 ??> 3 :: Maybe Ix3T
Just (2,0,3)
>>> arr !?> 2 ??> 0 ??> -1 :: Maybe Ix3T
Nothing
>>> arr !?> 2 ??> -10 ?? 1
*** Exception: IndexOutOfBoundsException: -10 is not safe for (Sz1 2)

Since: 0.1.0

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.

Since: 0.1.0

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

O(1) - Safe slice from the inside

Since: 0.1.0

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

O(1) - Safe slicing continuation from the inside

Since: 0.1.0

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.

Since: 0.1.0

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

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

Since: 0.1.0

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

O(1) - Safe slicing continuation from within.

Since: 0.1.0

Algorithms

Sorting

quicksort :: (Mutable r Ix1 e, Ord e) => Array r Ix1 e -> Array r Ix1 e Source #

This is an implementation of Quicksort, which is an efficient, but unstable sort that uses Median-of-three for pivot choosing, as such it performs very well not only for random values, but also for common edge cases like already sorted, reversed sorted and arrays with many duplicate elements. It will also respect the computation strategy and will result in a nice speed up for systems with multiple CPUs.

Since: 0.3.2

Iterations

iterateUntil Source #

Arguments

:: (Load r' ix e, Mutable r ix e) 
=> (Int -> Array r ix e -> Array r ix e -> Bool)

Convergence condition. Accepts current iteration counter, array at the previous state and at the current state.

-> (Int -> Array r ix e -> Array r' ix e)

A modifying function to apply at each iteration. The size of resulting array may differ if necessary

-> Array r ix e

Initial source array

-> Array r ix e 

Efficiently iterate a function until a convergence condition is satisfied. If the size of array doesn't change between iterations then no more than two new arrays will be allocated, regardless of the number of iterations. If the size does change from one iteration to another, an attempt will be made to grow/shrink the intermediate mutable array instead of allocating a new one.

Example

Expand
>>> import Data.Massiv.Array
>>> a = computeAs P $ makeLoadArrayS (Sz2 8 8) (0 :: Int) $ \ w -> w (0 :. 0) 1 >> pure ()
>>> a
Array P Seq (Sz (8 :. 8))
  [ [ 1, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0, 0, 0 ]
  ]
>>> nextPascalRow cur above = if cur == 0 then above else cur
>>> pascal = makeStencil (Sz2 2 2) 1 $ \ get -> nextPascalRow <$> get (0 :. 0) <*> get (-1 :. -1) + get (-1 :. 0)
>>> iterateUntil (\_ _ a -> (a ! (7 :. 7)) /= 0) (\ _ -> mapStencil (Fill 0) pascal) a
Array P Seq (Sz (8 :. 8))
  [ [ 1, 0, 0, 0, 0, 0, 0, 0 ]
  , [ 1, 1, 0, 0, 0, 0, 0, 0 ]
  , [ 1, 2, 1, 0, 0, 0, 0, 0 ]
  , [ 1, 3, 3, 1, 0, 0, 0, 0 ]
  , [ 1, 4, 6, 4, 1, 0, 0, 0 ]
  , [ 1, 5, 10, 10, 5, 1, 0, 0 ]
  , [ 1, 6, 15, 20, 15, 6, 1, 0 ]
  , [ 1, 7, 21, 35, 35, 21, 7, 1 ]
  ]

Since: 0.3.6

Conversion

List

fromList Source #

Arguments

:: Mutable r Ix1 e 
=> Comp

Computation startegy to use

-> [e]

Flat list

-> Array r Ix1 e 

Convert a flat list into a vector

Since: 0.1.0

fromListsM :: forall r ix e m. (Nested LN ix e, Ragged L ix e, Mutable r ix e, MonadThrow m) => Comp -> [ListItem ix e] -> m (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
>>> import Data.Massiv.Array as A
>>> fromListsM Seq [[1,2,3],[4,5,6]] :: Maybe (Array U Ix2 Int)
Just (Array U Seq (Sz (2 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  ]
)
>>> fromListsM Par [[[1,2,3]],[[4,5,6]]] :: Maybe (Array U Ix3 Int)
Just (Array U Par (Sz (2 :> 1 :. 3))
  [ [ [ 1, 2, 3 ]
    ]
  , [ [ 4, 5, 6 ]
    ]
  ]
)

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

>>> fromListsM Seq [[[1,2,3]],[[4,5]]] :: Maybe (Array B Ix2 [Int])
Just (Array B Seq (Sz (2 :. 1))
  [ [ [1,2,3] ]
  , [ [4,5] ]
  ]
)
>>> fromListsM Seq [[[1,2,3]],[[4,5]]] :: Maybe (Array B Ix3 Int)
Nothing
>>> fromListsM Seq [[[1,2,3]],[[4,5]]] :: IO (Array B Ix3 Int)
*** Exception: DimTooShortException: expected (Sz1 3), got (Sz1 2)

Since: 0.3.0

fromLists' Source #

Arguments

:: (Nested LN 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 fromListsM, but will throw a pure 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.

Examples

Expand

Convert a list of lists into a 2D Array

>>> import Data.Massiv.Array as A
>>> fromLists' Seq [[1,2,3],[4,5,6]] :: Array U Ix2 Int
Array U Seq (Sz (2 :. 3))
  [ [ 1, 2, 3 ]
  , [ 4, 5, 6 ]
  ]

Above example implemented using GHC's OverloadedLists extension:

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

Example of failure on conversion of an irregular nested list.

>>> fromLists' Seq [[1],[3,4]] :: Array U Ix2 Int
Array U *** Exception: DimTooLongException

Since: 0.1.0

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

Convert any array to a flat list.

Examples

Expand
>>> import Data.Massiv.Array
>>> toList $ makeArrayR U Seq (Sz (2 :. 3)) fromIx2
[(0,0),(0,1),(0,2),(1,0),(1,1),(1,2)]

Since: 0.1.0

toLists :: (Nested LN 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. Number of array dimensions 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
>>> import Data.Massiv.Array
>>> arr = makeArrayR U Seq (Sz (2 :> 1 :. 3)) id
>>> arr
Array U Seq (Sz (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]]]

Since: 0.1.0

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
>>> import Data.Massiv.Array
>>> toLists2 $ makeArrayR U Seq (Sz2 2 3) fromIx2
[[(0,0),(0,1),(0,2)],[(1,0),(1,1),(1,2)]]
>>> toLists2 $ makeArrayR U Seq (Sz3 2 1 3) fromIx3
[[(0,0,0),(0,0,1),(0,0,2)],[(1,0,0),(1,0,1),(1,0,2)]]

Since: 0.1.0

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.

Since: 0.1.0

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.

Since: 0.1.0

Mutable

Core

Representations

Stencil

Numeric Operations