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

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

Data.Massiv.Vector

Contents

Description

 
Synopsis

Documentation

type Vector r e = Array r Ix1 e Source #

Type synonym for a single dimension array, or simply a flat vector.

Since: 0.5.0

type MVector s r e = MArray s r Ix1 e Source #

Type synonym for a single dimension mutable array, or simply a flat mutable vector.

Since: 0.5.0

Accessors

Size

slength :: Stream r ix e => Array r ix e -> Maybe Sz1 Source #

O(1) - Get the length of a stream vector, but only if it is known excatly. Calling size will always give you the exact size instead, but for DS representation could result in evaluating of the whole stream.

Since: 0.5.0

snull :: Stream r ix e => Array r ix e -> Bool Source #

O(1) - Check if a stream array is empty.

Since: 0.5.0

Indexing

(!) :: 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) => 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

head' :: Source r Ix1 e => Vector r e -> e Source #

Get the first element of a Source vector. Throws an error on empty.

Since: 0.5.0

shead' :: Stream r Ix1 e => Vector r e -> e Source #

Get the first element of a Stream vector. Throws an error on empty.

Since: 0.5.0

last' :: Source r Ix1 e => Vector r e -> e Source #

Get the last element of a Source vector. Throws an error on empty.

Since: 0.5.0

Monadic Indexing

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

headM :: (Source r Ix1 e, MonadThrow m) => Vector r e -> m e Source #

Get the first element of a Source vector. Throws an error on empty.

Since: 0.5.0

sheadM :: (Stream r Ix1 e, MonadThrow m) => Vector r e -> m e Source #

Get the first element of a Stream vector. Throws an error on empty.

Since: 0.5.0

lastM :: (Source r Ix1 e, MonadThrow m) => Vector r e -> m e Source #

Get the last element of a Source vector. Throws an error on empty.

Since: 0.5.0

Slicing

slice :: Source r Ix1 e => Ix1 -> Sz1 -> Vector r e -> Vector r e Source #

O(1) - Take a slice of a Source vector. Never fails, instead adjusts the indices.

Since: 0.5.0

slice' :: Source r Ix1 e => Ix1 -> Sz1 -> Vector r e -> Vector r e Source #

O(1) - Take a slice of a Source vector. Throws an error on incorrect indices.

Since: 0.5.0

sliceM :: (Source r Ix1 e, MonadThrow m) => Ix1 -> Sz1 -> Vector r e -> m (Vector r e) Source #

O(1) - Take a slice of a Source vector. Throws an error on incorrect indices.

Since: 0.5.0

sslice :: Stream r Ix1 e => Ix1 -> Sz1 -> Vector r e -> Vector DS e Source #

O(1) - Take a slice of a Stream vector. Never fails, instead adjusts the indices.

Since: 0.5.0

sliceAt :: Source r Ix1 e => Sz1 -> Vector r e -> (Vector r e, Vector r e) Source #

Samel as sliceAt, except it never fails.

Since: 0.5.0

sliceAt' :: Source r Ix1 e => Sz1 -> Vector r e -> (Vector r e, Vector r e) Source #

Same as splitAt', except for a flat vector.

Since: 0.5.0

sliceAtM :: (Source r Ix1 e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e, Vector r e) Source #

Same as splitAtM, except for a flat vector.

Since: 0.5.0

Init

init :: Source r Ix1 e => Vector r e -> Vector r e Source #

O(1) - Get the vector without the last element. Never fails

Since: 0.5.0

init' :: Source r Ix1 e => Vector r e -> Vector r e Source #

O(1) - Get the vector without the last element. Throws an error on empty

Since: 0.5.0

initM :: (Source r Ix1 e, MonadThrow m) => Vector r e -> m (Vector r e) Source #

O(1) - Get the vector without the last element. Throws an error on empty

Since: 0.5.0

Tail

tail :: Source r Ix1 e => Vector r e -> Vector r e Source #

O(1) - Get the vector without the first element. Never fails

Since: 0.5.0

tail' :: Source r Ix1 e => Vector r e -> Vector r e Source #

O(1) - Get the vector without the first element. Throws an error on empty

Since: 0.5.0

tailM :: (Source r Ix1 e, MonadThrow m) => Vector r e -> m (Vector r e) Source #

O(1) - Get the vector without the first element. Throws an error on empty

Since: 0.5.0

Take

take :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e Source #

O(1) - Get the vector with the first n elements. Never fails

Since: 0.5.0

take' :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e Source #

O(1) - Get the vector with the first n elements. Throws an error size is less than n

Since: 0.5.0

takeM :: (Source r Ix1 e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e) Source #

O(1) - Get the vector with the first n elements. Throws an error size is less than n

Since: 0.5.0

stake :: Stream r Ix1 e => Sz1 -> Vector r e -> Vector DS e Source #

O(1) - Get a Stream vector with the first n elements. Never fails

Since: 0.5.0

Drop

drop :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e Source #

Since: 0.5.0

drop' :: Source r Ix1 e => Sz1 -> Vector r e -> Vector r e Source #

Since: 0.5.0

dropM :: (Source r Ix1 e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e) Source #

Since: 0.5.0

sdrop :: Stream r Ix1 e => Sz1 -> Vector r e -> Vector DS e Source #

Keep all but the first n elements from the delayed stream vector.

Since: 0.5.0

Construction

Initialization

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

sempty :: Vector DS e Source #

Create an empty delayed stream vector

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

ssingleton :: e -> Vector DS e Source #

Create a delayed stream vector with a single element

Since: 0.5.0

replicate :: forall ix e. Index ix => Comp -> Sz ix -> e -> Array DL ix e Source #

Replicate the same element

Since: 0.3.0

sreplicate :: Sz1 -> e -> Vector DS e Source #

Replicate the same element n times

Since: 0.5.0

generate :: Comp -> Sz1 -> (Ix1 -> e) -> Vector D e Source #

Create a delayed vector of length n with a function that maps an index to an element. Same as makeLinearArray

Since: 0.5.0

sgenerate :: Sz1 -> (Ix1 -> e) -> Vector DS e Source #

Create a delayed stream vector of length n with a function that maps an index to an element. Same as makeLinearArray

Since: 0.5.0

siterateN :: Sz1 -> (e -> e) -> e -> Vector DS e Source #

Create a delayed stream vector of length n by repeatedly apply a function to the initial value.

Since: 0.5.0

Monadic initialization

sreplicateM :: Monad m => Sz1 -> m e -> m (Vector DS e) Source #

Create a vector by using the same monadic action n times

Since: 0.5.0

sgenerateM :: Monad m => Sz1 -> (Ix1 -> m e) -> m (Vector DS e) Source #

Create a delayed stream vector of length n with a monadic action that from an index generates an element.

Since: 0.5.0

siterateNM :: Monad m => Sz1 -> (e -> m e) -> e -> m (Vector DS e) Source #

Create a delayed stream vector of length n by repeatedly apply a monadic action to the initial value.

Since: 0.5.0

Unfolding

sunfoldr :: (s -> Maybe (e, s)) -> s -> Vector DS e Source #

Right unfolding function. Useful when it is unknown ahead of time on how many elements the vector will have.

Example

Expand
>>> import Data.Massiv.Array as A
>>> sunfoldr (\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 ]

Since: 0.5.0

sunfoldrM :: Monad m => (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #

Same as unfoldr, by with monadic generating function.

Since: 0.5.0

sunfoldrN Source #

Arguments

:: Sz1

n - maximum number of elements that the vector will have

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

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

-> s

Inititial element.

-> Vector DS e 

O(n) - Right unfolding function with at most n number of elements.

Example

Expand
>>> import Data.Massiv.Array as A
>>> sunfoldrN 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.5.0

sunfoldrNM :: Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #

Same as unfoldrN, by with monadic generating function.

Since: 0.5.0

sunfoldrExactN :: Sz1 -> (s -> (e, s)) -> s -> Vector DS e Source #

Similar to unfoldrN, except the length of the resulting vector will be exactly n

Since: 0.5.0

sunfoldrExactNM :: Monad m => Sz1 -> (s -> m (e, s)) -> s -> m (Vector DS e) Source #

Similar to unfoldrNM, except the length of the resulting vector will be exactly n

Since: 0.5.0

senumFromN :: Num e => e -> Sz1 -> Vector DS e Source #

Enumerate from a starting number n times with a step 1

Since: 0.5.0

senumFromStepN Source #

Arguments

:: Num e 
=> e

Starting value

-> e

Step

-> Sz1

Resulting length of a vector

-> Vector DS e 

Enumerate from a starting number n times with a custom step value

Since: 0.5.0

Concatenation

sappend :: (Stream r1 Ix1 e, Stream r2 Ix1 e) => Vector r1 e -> Vector r2 e -> Vector DS e Source #

Append two vectors together

Since: 0.5.0

sconcat :: Stream r Ix1 e => [Vector r e] -> Vector DS e Source #

Concat vectors together

Since: 0.5.0

smap :: Stream r ix a => (a -> b) -> Array r ix a -> Vector DS b Source #

Map a function over a stream vector

Since: 0.5.0

simap :: Stream r ix a => (ix -> a -> b) -> Array r ix a -> Vector DS b Source #

Map an index aware function over a stream vector

Since: 0.5.0

Monadic mapping

straverse :: (Stream r ix a, Applicative f) => (a -> f b) -> Array r ix a -> f (Vector DS b) Source #

Traverse a stream vector with an applicative function.

Since: 0.5.0

sitraverse :: (Stream r ix a, Applicative f) => (ix -> a -> f b) -> Array r ix a -> f (Vector DS b) Source #

Traverse a stream vector with an index aware applicative function.

Since: 0.5.0

smapM :: (Stream r ix a, Monad m) => (a -> m b) -> Array r ix a -> m (Vector DS b) Source #

Traverse a stream vector with a monadic function.

Since: 0.5.0

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

Traverse a stream vector with a monadic function, while discarding the result

Since: 0.5.0

simapM :: (Stream r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m (Vector DS b) Source #

Traverse a stream vector with a monadic index aware function.

Since: 0.5.0

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

Traverse a stream vector with a monadic index aware function, while discarding the result

Since: 0.5.0

sforM :: (Stream r ix a, Monad m) => Array r ix a -> (a -> m b) -> m (Vector DS b) Source #

Same as smapM, but with arguments flipped.

Since: 0.5.0

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

Same as smapM_, but with arguments flipped.

Since: 0.5.0

siforM :: (Stream r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m (Vector DS b) Source #

Same as simapM, but with arguments flipped.

Since: 0.5.0

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

Same as simapM_, but with arguments flipped.

Since: 0.5.0

Zipping

szip :: (Stream ra ixa a, Stream rb ixb b) => Array ra ixa a -> Array rb ixb b -> Vector DS (a, b) Source #

Since: 0.5.0

szip3 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c) => Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Vector DS (a, b, c) Source #

Since: 0.5.0

szip4 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d) => Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Vector DS (a, b, c, d) Source #

Since: 0.5.0

szip5 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e) => Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Vector DS (a, b, c, d, e) Source #

Since: 0.5.0

szip6 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Stream rf ixf f) => Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Array rf ixf f -> Vector DS (a, b, c, d, e, f) Source #

Since: 0.5.0

szipWith :: (Stream ra ixa a, Stream rb ixb b) => (a -> b -> c) -> Array ra ixa a -> Array rb ixb b -> Vector DS c Source #

Since: 0.5.0

szipWith3 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c) => (a -> b -> c -> d) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Vector DS d Source #

Since: 0.5.0

szipWith4 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d) => (a -> b -> c -> d -> e) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Vector DS e Source #

Since: 0.5.0

szipWith5 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e) => (a -> b -> c -> d -> e -> f) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Vector DS f Source #

Since: 0.5.0

szipWith6 :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Stream rf ixf f) => (a -> b -> c -> d -> e -> f -> g) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Array rf ixf f -> Vector DS g Source #

Since: 0.5.0

sizipWith :: (Stream ra ix a, Stream rb ix b) => (ix -> a -> b -> c) -> Array ra ix a -> Array rb ix b -> Vector DS c Source #

Since: 0.5.0

sizipWith3 :: (Stream ra ix a, Stream rb ix b, Stream rc ix c) => (ix -> a -> b -> c -> d) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Vector DS d Source #

Since: 0.5.0

sizipWith4 :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d) => (ix -> a -> b -> c -> d -> e) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Vector DS e Source #

Since: 0.5.0

sizipWith5 :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e) => (ix -> a -> b -> c -> d -> e -> f) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> Vector DS f Source #

Since: 0.5.0

sizipWith6 :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e, Stream rf ix f) => (ix -> a -> b -> c -> d -> e -> f -> g) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> Array rf ix f -> Vector DS g Source #

Since: 0.5.0

Monadic zipping

szipWithM :: (Stream ra ixa a, Stream rb ixb b, Monad m) => (a -> b -> m c) -> Array ra ixa a -> Array rb ixb b -> m (Vector DS c) Source #

Since: 0.5.0

szipWith3M :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Monad m) => (a -> b -> c -> m d) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> m (Vector DS d) Source #

Since: 0.5.0

szipWith4M :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Monad m) => (a -> b -> c -> d -> m e) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> m (Vector DS e) Source #

Since: 0.5.0

szipWith5M :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> m (Vector DS f) Source #

Since: 0.5.0

szipWith6M :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Stream rf ixf f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Array rf ixf f -> m (Vector DS g) Source #

Since: 0.5.0

sizipWithM :: (Stream ra ix a, Stream rb ix b, Monad m) => (ix -> a -> b -> m c) -> Array ra ix a -> Array rb ix b -> m (Vector DS c) Source #

Since: 0.5.0

sizipWith3M :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Monad m) => (ix -> a -> b -> c -> m d) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> m (Vector DS d) Source #

Since: 0.5.0

sizipWith4M :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Monad m) => (ix -> a -> b -> c -> d -> m e) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> m (Vector DS e) Source #

Since: 0.5.0

sizipWith5M :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e, Monad m) => (ix -> a -> b -> c -> d -> e -> m f) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> m (Vector DS f) Source #

Since: 0.5.0

sizipWith6M :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e, Stream rf ix f, Monad m) => (ix -> a -> b -> c -> d -> e -> f -> m g) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> Array rf ix f -> m (Vector DS g) Source #

Since: 0.5.0

szipWithM_ :: (Stream ra ixa a, Stream rb ixb b, Monad m) => (a -> b -> m c) -> Array ra ixa a -> Array rb ixb b -> m () Source #

Since: 0.5.0

szipWith3M_ :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Monad m) => (a -> b -> c -> m d) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> m () Source #

Since: 0.5.0

szipWith4M_ :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Monad m) => (a -> b -> c -> d -> m e) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> m () Source #

Since: 0.5.0

szipWith5M_ :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> m () Source #

Since: 0.5.0

szipWith6M_ :: (Stream ra ixa a, Stream rb ixb b, Stream rc ixc c, Stream rd ixd d, Stream re ixe e, Stream rf ixf f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Array ra ixa a -> Array rb ixb b -> Array rc ixc c -> Array rd ixd d -> Array re ixe e -> Array rf ixf f -> m () Source #

Since: 0.5.0

sizipWithM_ :: (Stream ra ix a, Stream rb ix b, Monad m) => (ix -> a -> b -> m c) -> Array ra ix a -> Array rb ix b -> m () Source #

Since: 0.5.0

sizipWith3M_ :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Monad m) => (ix -> a -> b -> c -> m d) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> m () Source #

Since: 0.5.0

sizipWith4M_ :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Monad m) => (ix -> a -> b -> c -> d -> m e) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> m () Source #

Since: 0.5.0

sizipWith5M_ :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e, Monad m) => (ix -> a -> b -> c -> d -> e -> m f) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> m () Source #

Since: 0.5.0

sizipWith6M_ :: (Stream ra ix a, Stream rb ix b, Stream rc ix c, Stream rd ix d, Stream re ix e, Stream rf ix f, Monad m) => (ix -> a -> b -> c -> d -> e -> f -> m g) -> Array ra ix a -> Array rb ix b -> Array rc ix c -> Array rd ix d -> Array re ix e -> Array rf ix f -> m () Source #

Since: 0.5.0

Predicates

Filtering

sfilter :: Stream r ix e => (e -> Bool) -> Array r ix e -> Vector DS 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) ]
  ]
>>> sfilter (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.5.0

sifilter :: Stream r ix a => (ix -> a -> Bool) -> Array r ix a -> Vector DS a Source #

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

Since: 0.5.0

sfilterM :: (Stream r ix e, Applicative f) => (e -> f Bool) -> Array r ix e -> f (Vector DS 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) ]
  ]
>>> sfilterM (Just . odd . fst) arr
Just (Array DS Seq (Sz1 4)
  [ (1,0), (1,1), (1,2), (1,3) ]
)
>>> sfilterM (\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.5.0

sifilterM :: (Stream r ix a, Applicative f) => (ix -> a -> f Bool) -> Array r ix a -> f (Vector DS a) Source #

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

Since: 0.5.0

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

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

Since: 0.5.0

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

Similar to smapMaybe, but with the use of Applicative

Since: 0.5.0

scatMaybes :: Stream r ix (Maybe a) => Array r ix (Maybe a) -> Vector DS a Source #

Keep all Maybes and discard the Nothings.

Since: 0.5.0

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

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

Since: 0.5.0

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

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

Since: 0.5.0

Folding

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

sfoldl1' :: Stream r ix e => (e -> e -> e) -> Array r ix e -> e Source #

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

Specialized folds

sor :: Stream r ix Bool => Array r ix Bool -> Bool Source #

Since: 0.5.0

sand :: Stream r ix Bool => Array r ix Bool -> Bool Source #

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

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

Since: 0.5.0

Conversions

Lists

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

Convert an array to a list by the means of a delayed stream vector.

Since: 0.5.0

sfromList :: [e] -> Vector DS e Source #

Convert a list to a delayed stream vector

Since: 0.5.0

sfromListN :: Int -> [e] -> Vector DS e Source #

Convert a list of a known length to a delayed stream vector

Since: 0.5.0

Deprecated

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

Deprecated: In favor of stake

See stake.

Since: 0.4.1

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

Deprecated: In favor of sdrop

See sdrop.

Since: 0.4.1

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

Deprecated: In favor of sunfoldr

See sunfoldr

Since: 0.4.1

unfoldrN :: Sz1 -> (s -> Maybe (e, s)) -> s -> Vector DS e Source #

Deprecated: In favor of sunfoldrN

See sunfoldrN

Since: 0.4.1

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

Deprecated: In favor of sfilter

See sfilter

Since: 0.4.1

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

Deprecated: In favor of sifilter

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 (Vector DS e) Source #

Deprecated: In favor of sfilterM

See sfilterM

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 #

Deprecated: In favor of sifilterM

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

Since: 0.4.1

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

Deprecated: In favor of smapMaybe

See smapMaybe

Since: 0.4.1

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

Deprecated: In favor of simapMaybe

See simapMaybe

Since: 0.4.1

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

Deprecated: In favor of smapMaybeM

See smapMaybeM

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 #

Deprecated: In favor of simapMaybeM

See simapMaybeM

Since: 0.4.1

catMaybesS :: Stream r ix (Maybe a) => Array r ix (Maybe a) -> Vector DS a Source #

Deprecated: In favor of scatMaybes

See scatMaybes

Since: 0.4.4

traverseS :: (Stream r ix a, Applicative f) => (a -> f b) -> Array r ix a -> f (Vector DS b) Source #

Deprecated: In favor of straverse

See traverseS

Since: 0.4.5