Copyright | (c) Alexey Kuleshevich 2018-2022 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Massiv is a library, that allows creation and manipulation of arrays in parallel and
sequentially. Depending on the representation (r
), an
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 (Array
r ix eix
) 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).BN
- Similar toB
, it is also a boxed type, except its elements are always kept in a Normal Form (NF). This property is very useful for parallel processing, i.e. when callingcompute
you do want all of your elements to be fully evaluated.BL
- Similar toB
, it is also a boxed type, but lazy. Its elements are not evaluated when array is computed.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 ofStorable
class. It is just as efficient asP
andU
arrays, except it is subject to fragmentation.U
- Unboxed representation. Elements must be an instance ofUnbox
class.P
- Array that can hold Haskell primitives, such asInt
,Word
,Double
, etc. Any element must be an instance ofPrim
class.
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. UsecomputeAs
in order to load array intoManifest
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. UsecomputeAs
in order to load array intoManifest
representation.DS
- delayed stream vector representation that describes how to handle a vector with possibility of unknown length. Useful for filtering and unfolding. UsecomputeAs
in order to load such vector intoManifest
representation.DI
- delayed interleaved array. Same asD
, 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 fastStencil
computation.
Other Array types:
L
- this type isn't particularly useful on its own, but because it has unique ability to be converted to and from nested lists in constant time, it provides a perfect intermediary for conversion of nested lists into manifest arrays.
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
- empty :: forall r ix e. Load r ix e => Array r ix e
- singleton :: forall r ix e. Load r ix e => e -> Array r ix e
- replicate :: Load r ix e => Comp -> Sz ix -> e -> Array r ix e
- makeArray :: Load r ix e => Comp -> Sz ix -> (ix -> e) -> Array r ix e
- makeArrayLinear :: Load r ix e => Comp -> Sz ix -> (Int -> e) -> Array r ix e
- makeArrayR :: Load r ix e => r -> Comp -> Sz ix -> (ix -> e) -> Array r ix e
- makeArrayLinearR :: Load r ix e => r -> Comp -> Sz ix -> (Int -> e) -> Array r ix e
- makeVectorR :: Load r Ix1 e => r -> Comp -> Sz1 -> (Ix1 -> e) -> Vector r e
- iterateN :: forall ix e. Index ix => Sz ix -> (e -> e) -> e -> Array DL ix e
- iiterateN :: forall ix e. Index ix => Sz ix -> (e -> ix -> e) -> e -> Array DL ix e
- unfoldlS_ :: Index ix => Sz ix -> (a -> (a, e)) -> a -> Array DL ix e
- iunfoldlS_ :: forall ix e a. Index ix => Sz ix -> (ix -> a -> (a, e)) -> a -> Array DL ix e
- unfoldrS_ :: forall ix e a. Index ix => Sz ix -> (a -> (e, a)) -> a -> Array DL ix e
- iunfoldrS_ :: forall ix e a. Index ix => Sz ix -> (a -> ix -> (e, a)) -> a -> Array DL ix e
- makeSplitSeedArray :: forall ix e g it. (Iterator it, Index ix) => it -> g -> (g -> (g, g)) -> Comp -> Sz ix -> (Ix1 -> ix -> g -> (e, g)) -> Array DL ix e
- uniformArray :: forall ix e g. (Index ix, RandomGen g, Uniform e) => g -> Comp -> Sz ix -> Array DL ix e
- uniformRangeArray :: forall ix e g. (Index ix, RandomGen g, UniformRange e) => g -> (e, e) -> Comp -> Sz ix -> Array DL ix e
- randomArray :: forall ix e g. Index ix => g -> (g -> (g, g)) -> (g -> (e, g)) -> Comp -> Sz ix -> Array DL ix e
- randomArrayS :: forall r ix e g. (Manifest r e, Index ix) => g -> Sz ix -> (g -> (e, g)) -> (g, Array r ix e)
- randomArrayWS :: forall r ix e g m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates g -> Sz ix -> (g -> m e) -> m (Array r ix e)
- makeArrayA :: forall r ix e f. (Manifest r e, Index ix, Applicative f) => Sz ix -> (ix -> f e) -> f (Array r ix e)
- makeArrayAR :: forall r ix e f. (Manifest r e, Index ix, Applicative f) => r -> Sz ix -> (ix -> f e) -> f (Array r ix e)
- makeArrayLinearA :: forall r ix e f. (Manifest r e, Index ix, Applicative f) => Sz ix -> (Int -> f e) -> f (Array r ix e)
- (...) :: Index ix => ix -> ix -> Array D ix ix
- (..:) :: Index ix => ix -> ix -> Array D ix ix
- range :: Index ix => Comp -> ix -> ix -> Array D ix ix
- rangeStepM :: forall ix m. (Index ix, MonadThrow m) => Comp -> ix -> ix -> ix -> m (Array D ix ix)
- rangeStep' :: (HasCallStack, Index ix) => Comp -> ix -> ix -> ix -> Array D ix ix
- rangeInclusive :: Index ix => Comp -> ix -> ix -> Array D ix ix
- rangeStepInclusiveM :: (MonadThrow m, Index ix) => Comp -> ix -> ix -> ix -> m (Array D ix ix)
- rangeStepInclusive' :: (HasCallStack, Index ix) => Comp -> ix -> ix -> ix -> Array D ix ix
- rangeSize :: Index ix => Comp -> ix -> Sz ix -> Array D ix ix
- rangeStepSize :: Index ix => Comp -> ix -> ix -> Sz ix -> Array D ix ix
- enumFromN :: Num e => Comp -> e -> Sz1 -> Vector D e
- enumFromStepN :: Num e => Comp -> e -> e -> Sz1 -> Vector D e
- expandWithin :: forall n ix e r a. (IsIndexDimension ix n, Index (Lower ix), Manifest r a) => Dimension n -> Sz1 -> (a -> Ix1 -> e) -> Array r (Lower ix) a -> Array D ix e
- expandWithinM :: forall r ix a b m. (Index ix, Index (Lower ix), Manifest r a, MonadThrow m) => Dim -> Sz1 -> (a -> Ix1 -> b) -> Array r (Lower ix) a -> m (Array D ix b)
- expandWithin' :: forall r ix a b. (HasCallStack, Index ix, Index (Lower ix), Manifest r a) => Dim -> Sz1 -> (a -> Ix1 -> b) -> Array r (Lower ix) a -> Array D ix b
- expandOuter :: forall r ix a b. (Index ix, Index (Lower ix), Manifest r a) => Sz1 -> (a -> Ix1 -> b) -> Array r (Lower ix) a -> Array D ix b
- expandInner :: forall r ix a b. (Index ix, Index (Lower ix), Manifest r a) => Sz1 -> (a -> Ix1 -> b) -> Array r (Lower ix) a -> Array D ix b
- getComp :: Strategy r => Array r ix e -> Comp
- setComp :: Strategy r => Comp -> Array r ix e -> Array r ix e
- appComp :: Strategy r => Comp -> Array r ix e -> Array r ix e
- compute :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e
- computeS :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e
- computeP :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e
- computeIO :: forall r ix e r' m. (Manifest r e, Load r' ix e, MonadIO m) => Array r' ix e -> m (Array r ix e)
- computePrimM :: forall r ix e r' m. (Manifest r e, Load r' ix e, PrimMonad m) => Array r' ix e -> m (Array r ix e)
- computeAs :: (Manifest r e, Load r' ix e) => r -> Array r' ix e -> Array r ix e
- computeProxy :: (Manifest r e, Load r' ix e) => proxy r -> Array r' ix e -> Array r ix e
- computeSource :: forall r ix e r'. (Manifest r e, Source r' e, Index ix) => Array r' ix e -> Array r ix e
- computeWithStride :: forall r ix e r'. (Manifest r e, StrideLoad r' ix e) => Stride ix -> Array r' ix e -> Array r ix e
- computeWithStrideAs :: (Manifest r e, StrideLoad r' ix e) => r -> Stride ix -> Array r' ix e -> Array r ix e
- clone :: (Manifest r e, Index ix) => Array r ix e -> Array r ix e
- convert :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e
- convertAs :: (Manifest r e, Load r' ix e) => r -> Array r' ix e -> Array r ix e
- convertProxy :: (Manifest r e, Load r' ix e) => proxy r -> Array r' ix e -> Array r ix e
- fromRaggedArrayM :: forall r ix e r' m. (Manifest r e, Ragged r' ix e, MonadThrow m) => Array r' ix e -> m (Array r ix e)
- fromRaggedArray' :: forall r ix e r'. (HasCallStack, Manifest r e, Ragged r' ix e) => Array r' ix e -> Array r ix e
- module Data.Massiv.Vector
- size :: Size r => Array r ix e -> Sz ix
- elemsCount :: (Index ix, Size r) => Array r ix e -> Int
- isEmpty :: (Index ix, Size r) => Array r ix e -> Bool
- isNotEmpty :: (Index ix, Size r) => Array r ix e -> Bool
- isNull :: Shape r ix => Array r ix e -> Bool
- isNotNull :: Shape r ix => Array r ix e -> Bool
- (!?) :: forall r ix e m. (Index ix, Manifest r e, MonadThrow m) => Array r ix e -> ix -> m e
- (!) :: forall r ix e. (HasCallStack, Manifest r e, Index ix) => Array r ix e -> ix -> e
- (??) :: (Index ix, Manifest r e, MonadThrow m) => m (Array r ix e) -> ix -> m e
- indexM :: (Index ix, Manifest r e, MonadThrow m) => Array r ix e -> ix -> m e
- index :: (Index ix, Manifest r e) => Array r ix e -> ix -> Maybe e
- index' :: (HasCallStack, Index ix, Manifest r e) => Array r ix e -> ix -> e
- defaultIndex :: (Index ix, Manifest r e) => e -> Array r ix e -> ix -> e
- borderIndex :: (Index ix, Manifest r e) => Border e -> Array r ix e -> ix -> e
- evaluateM :: (Index ix, Source r e, MonadThrow m) => Array r ix e -> ix -> m e
- evaluate' :: (HasCallStack, Index ix, Source r e) => Array r ix e -> ix -> e
- map :: (Index ix, Source r e') => (e' -> e) -> Array r ix e' -> Array D ix e
- imap :: forall r ix e a. (Index ix, Source r e) => (ix -> e -> a) -> Array r ix e -> Array D ix a
- traverseA :: forall r ix e r' a f. (Source r' a, Manifest r e, Index ix, Applicative f) => (a -> f e) -> Array r' ix a -> f (Array r ix e)
- traverseA_ :: forall r ix e a f. (Index ix, Source r e, Applicative f) => (e -> f a) -> Array r ix e -> f ()
- itraverseA :: forall r ix e r' a f. (Source r' a, Manifest r e, Index ix, Applicative f) => (ix -> a -> f e) -> Array r' ix a -> f (Array r ix e)
- itraverseA_ :: forall r ix e a f. (Source r a, Index ix, Applicative f) => (ix -> a -> f e) -> Array r ix a -> f ()
- sequenceA :: forall r ix e r' f. (Source r' (f e), Manifest r e, Index ix, Applicative f) => Array r' ix (f e) -> f (Array r ix e)
- sequenceA_ :: forall r ix e f. (Index ix, Source r (f e), Applicative f) => Array r ix (f e) -> f ()
- traversePrim :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, PrimMonad m) => (a -> m b) -> Array r' ix a -> m (Array r ix b)
- itraversePrim :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, PrimMonad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b)
- mapM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => (a -> m b) -> Array r' ix a -> m (Array r ix b)
- forM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => Array r' ix a -> (a -> m b) -> m (Array r ix b)
- imapM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b)
- iforM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => Array r' ix a -> (ix -> a -> m b) -> m (Array r ix b)
- mapM_ :: (Source r a, Index ix, Monad m) => (a -> m b) -> Array r ix a -> m ()
- forM_ :: (Source r a, Index ix, Monad m) => Array r ix a -> (a -> m b) -> m ()
- imapM_ :: (Index ix, Source r a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m ()
- iforM_ :: (Source r a, Index ix, Monad m) => Array r ix a -> (ix -> a -> m b) -> m ()
- mapIO :: forall r ix b r' a m. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO m) => (a -> m b) -> Array r' ix a -> m (Array r ix b)
- mapWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> (a -> s -> m b) -> Array r' ix a -> m (Array r ix b)
- mapIO_ :: forall r ix e a m. (Load r ix e, MonadUnliftIO m) => (e -> m a) -> Array r ix e -> m ()
- imapIO :: forall r ix b r' a m. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b)
- imapWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> (ix -> a -> s -> m b) -> Array r' ix a -> m (Array r ix b)
- imapIO_ :: forall r ix e a m. (Load r ix e, MonadUnliftIO m) => (ix -> e -> m a) -> Array r ix e -> m ()
- forIO :: forall r ix b r' a m. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO m) => Array r' ix a -> (a -> m b) -> m (Array r ix b)
- forWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Array r' ix a -> (a -> s -> m b) -> m (Array r ix b)
- forIO_ :: (Load r ix e, MonadUnliftIO m) => Array r ix e -> (e -> m a) -> m ()
- iforIO :: forall r ix b r' a m. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO m) => Array r' ix a -> (ix -> a -> m b) -> m (Array r ix b)
- iforWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Array r' ix a -> (ix -> a -> s -> m b) -> m (Array r ix b)
- iforIO_ :: forall r ix e a m. (Load r ix e, MonadUnliftIO m) => Array r ix e -> (ix -> e -> m a) -> m ()
- imapSchedulerM_ :: (Index ix, Source r e, MonadPrimBase s m) => Scheduler s () -> (ix -> e -> m a) -> Array r ix e -> m ()
- iforSchedulerM_ :: (Index ix, Source r e, MonadPrimBase s m) => Scheduler s () -> Array r ix e -> (ix -> e -> m a) -> m ()
- iterArrayLinearM_ :: forall r ix e m s. (Load r ix e, MonadPrimBase s m) => Scheduler s () -> Array r ix e -> (Int -> e -> m ()) -> m ()
- iterArrayLinearWithSetM_ :: forall r ix e m s. (Load r ix e, MonadPrimBase s m) => Scheduler s () -> Array r ix e -> (Int -> e -> m ()) -> (Ix1 -> Sz1 -> e -> m ()) -> m ()
- iterArrayLinearWithStrideM_ :: forall r ix e m s. (StrideLoad r ix e, MonadPrimBase s m) => Scheduler s () -> Stride ix -> Sz ix -> Array r ix e -> (Int -> e -> m ()) -> m ()
- zip :: (Index ix, Source r1 e1, Source r2 e2) => Array r1 ix e1 -> Array r2 ix e2 -> Array D ix (e1, e2)
- zip3 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3) => Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix (e1, e2, e3)
- zip4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix (e1, e2, e3, e4)
- unzip :: (Index ix, Source r (e1, e2)) => Array r ix (e1, e2) -> (Array D ix e1, Array D ix e2)
- unzip3 :: (Index ix, Source r (e1, e2, e3)) => Array r ix (e1, e2, e3) -> (Array D ix e1, Array D ix e2, Array D ix e3)
- unzip4 :: (Index ix, Source r (e1, e2, e3, e4)) => Array r ix (e1, e2, e3, e4) -> (Array D ix e1, Array D ix e2, Array D ix e3, Array D ix e4)
- zipWith :: (Index ix, Source r1 e1, Source r2 e2) => (e1 -> e2 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array D ix e
- zipWith3 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3) => (e1 -> e2 -> e3 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix e
- zipWith4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => (e1 -> e2 -> e3 -> e4 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix e
- izipWith :: (Index ix, Source r1 e1, Source r2 e2) => (ix -> e1 -> e2 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array D ix e
- izipWith3 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3) => (ix -> e1 -> e2 -> e3 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix e
- izipWith4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => (ix -> e1 -> e2 -> e3 -> e4 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix e
- zipWithA :: (Source r1 e1, Source r2 e2, Applicative f, Manifest r e, Index ix) => (e1 -> e2 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> f (Array r ix e)
- izipWithA :: (Source r1 e1, Source r2 e2, Applicative f, Manifest r e, Index ix) => (ix -> e1 -> e2 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> f (Array r ix e)
- zipWith3A :: (Source r1 e1, Source r2 e2, Source r3 e3, Applicative f, Manifest r e, Index ix) => (e1 -> e2 -> e3 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> f (Array r ix e)
- izipWith3A :: (Source r1 e1, Source r2 e2, Source r3 e3, Applicative f, Manifest r e, Index ix) => (ix -> e1 -> e2 -> e3 -> f e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> f (Array r ix e)
- fold :: (Monoid e, Index ix, Source r e) => Array r ix e -> e
- ifoldMono :: (Index ix, Source r e, Monoid m) => (ix -> e -> m) -> Array r ix e -> m
- foldMono :: (Index ix, Source r e, Monoid m) => (e -> m) -> Array r ix e -> m
- ifoldSemi :: (Index ix, Source r e, Semigroup m) => (ix -> e -> m) -> m -> Array r ix e -> m
- foldSemi :: (Index ix, Source r e, Semigroup m) => (e -> m) -> m -> Array r ix e -> m
- foldOuterSlice :: (Index ix, Index (Lower ix), Source r e, Monoid m) => (Array r (Lower ix) e -> m) -> Array r ix e -> m
- ifoldOuterSlice :: (Index ix, Index (Lower ix), Source r e, Monoid m) => (Ix1 -> Array r (Lower ix) e -> m) -> Array r ix e -> m
- foldInnerSlice :: (Source r e, Index ix, Monoid m) => (Array D (Lower ix) e -> m) -> Array r ix e -> m
- ifoldInnerSlice :: (Source r e, Index ix, Monoid m) => (Ix1 -> Array D (Lower ix) e -> m) -> Array r ix e -> m
- minimumM :: (MonadThrow m, Shape r ix, Source r e, Ord e) => Array r ix e -> m e
- minimum' :: forall r ix e. (HasCallStack, Shape r ix, Source r e, Ord e) => Array r ix e -> e
- maximumM :: (MonadThrow m, Shape r ix, Source r e, Ord e) => Array r ix e -> m e
- maximum' :: forall r ix e. (HasCallStack, Shape r ix, Source r e, Ord e) => Array r ix e -> e
- sum :: (Index ix, Source r e, Num e) => Array r ix e -> e
- product :: (Index ix, Source r e, Num e) => Array r ix e -> e
- and :: (Index ix, Source r Bool) => Array r ix Bool -> Bool
- or :: (Index ix, Source r Bool) => Array r ix Bool -> Bool
- all :: (Index ix, Source r e) => (e -> Bool) -> Array r ix e -> Bool
- any :: (Index ix, Source r e) => (e -> Bool) -> Array r ix e -> Bool
- elem :: (Eq e, Index ix, Source r e) => e -> Array r ix e -> Bool
- eqArrays :: (Index ix, Source r1 e1, Source r2 e2) => (e1 -> e2 -> Bool) -> Array r1 ix e1 -> Array r2 ix e2 -> Bool
- compareArrays :: (Index ix, Source r1 e1, Source r2 e2) => (e1 -> e2 -> Ordering) -> Array r1 ix e1 -> Array r2 ix e2 -> Ordering
- ifoldlInner :: (Index (Lower ix), Index ix, Source r e) => (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldlInner :: (Index (Lower ix), Index ix, Source r e) => (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- ifoldrInner :: (Index (Lower ix), Index ix, Source r e) => (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldrInner :: (Index (Lower ix), Index ix, Source r e) => (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldInner :: (Monoid e, Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D (Lower ix) e
- ifoldlWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r e) => Dimension n -> (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldlWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r e) => Dimension n -> (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- ifoldrWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r e) => Dimension n -> (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldrWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r e) => Dimension n -> (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldWithin :: (Source r a, Monoid a, Index (Lower ix), IsIndexDimension ix n) => Dimension n -> Array r ix a -> Array D (Lower ix) a
- ifoldlWithin' :: (HasCallStack, Index (Lower ix), Index ix, Source r e) => Dim -> (ix -> a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldlWithin' :: (HasCallStack, Index (Lower ix), Index ix, Source r e) => Dim -> (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- ifoldrWithin' :: (HasCallStack, Index (Lower ix), Index ix, Source r e) => Dim -> (ix -> e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldrWithin' :: (HasCallStack, Index (Lower ix), Index ix, Source r e) => Dim -> (e -> a -> a) -> a -> Array r ix e -> Array D (Lower ix) a
- foldWithin' :: (HasCallStack, Index ix, Source r a, Monoid a, Index (Lower ix)) => Dim -> Array r ix a -> Array D (Lower ix) a
- foldlS :: (Index ix, Source r e) => (a -> e -> a) -> a -> Array r ix e -> a
- foldrS :: (Index ix, Source r e) => (e -> a -> a) -> a -> Array r ix e -> a
- ifoldlS :: (Index ix, Source r e) => (a -> ix -> e -> a) -> a -> Array r ix e -> a
- ifoldrS :: (Index ix, Source r e) => (ix -> e -> a -> a) -> a -> Array r ix e -> a
- foldlM :: (Index ix, Source r e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m a
- foldrM :: (Index ix, Source r e, Monad m) => (e -> a -> m a) -> a -> Array r ix e -> m a
- foldlM_ :: (Index ix, Source r e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m ()
- foldrM_ :: (Index ix, Source r e, Monad m) => (e -> a -> m a) -> a -> Array r ix e -> m ()
- ifoldlM :: (Index ix, Source r e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m a
- ifoldrM :: (Index ix, Source r e, Monad m) => (ix -> e -> a -> m a) -> a -> Array r ix e -> m a
- ifoldlM_ :: (Index ix, Source r e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m ()
- ifoldrM_ :: (Index ix, Source r e, Monad m) => (ix -> e -> a -> m a) -> a -> Array r ix e -> m ()
- foldrFB :: (Index ix, Source r e) => (e -> b -> b) -> b -> Array r ix e -> b
- lazyFoldlS :: (Index ix, Source r e) => (a -> e -> a) -> a -> Array r ix e -> a
- lazyFoldrS :: (Index ix, Source r e) => (e -> a -> a) -> a -> Array r ix e -> a
- foldlP :: (MonadIO m, Index ix, Source r e) => (a -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> m b
- foldrP :: (MonadIO m, Index ix, Source r e) => (e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> m b
- ifoldlP :: (MonadIO m, Index ix, Source r e) => (a -> ix -> e -> a) -> a -> (b -> a -> b) -> b -> Array r ix e -> m b
- ifoldrP :: (MonadIO m, Index ix, Source r e) => (ix -> e -> a -> a) -> a -> (a -> b -> b) -> b -> Array r ix e -> m b
- ifoldlIO :: (MonadUnliftIO m, Index ix, Source r e) => (a -> ix -> e -> m a) -> a -> (b -> a -> m b) -> b -> Array r ix e -> m b
- ifoldrIO :: (MonadUnliftIO m, Index ix, Source r e) => (ix -> e -> a -> m a) -> a -> (a -> b -> m b) -> b -> Array r ix e -> m b
- transpose :: forall r e. Source r e => Matrix r e -> Matrix D e
- transposeInner :: forall r ix e. (Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D ix e
- transposeOuter :: forall r ix e. (Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D ix e
- reverse :: forall n r ix e. (IsIndexDimension ix n, Index ix, Source r e) => Dimension n -> Array r ix e -> Array D ix e
- reverse' :: forall r ix e. (HasCallStack, Index ix, Source r e) => Dim -> Array r ix e -> Array D ix e
- reverseM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Dim -> Array r ix e -> m (Array D ix e)
- backpermuteM :: forall r ix e r' ix' m. (Manifest r e, Index ix, Source r' e, Index ix', MonadUnliftIO m, PrimMonad m, MonadThrow m) => Sz ix -> (ix -> ix') -> Array r' ix' e -> m (Array r ix e)
- backpermute' :: forall r ix ix' e. (HasCallStack, Source r e, Index ix, Index ix') => Sz ix' -> (ix' -> ix) -> Array r ix e -> Array D ix' e
- resizeM :: forall r ix ix' e m. (MonadThrow m, Index ix', Index ix, Size r) => Sz ix' -> Array r ix e -> m (Array r ix' e)
- resize' :: forall r ix ix' e. (HasCallStack, Index ix', Index ix, Size r) => Sz ix' -> Array r ix e -> Array r ix' e
- flatten :: forall r ix e. (Index ix, Size r) => Array r ix e -> Vector r e
- extractM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => ix -> Sz ix -> Array r ix e -> m (Array D ix e)
- extract' :: forall r ix e. (HasCallStack, Index ix, Source r e) => ix -> Sz ix -> Array r ix e -> Array D ix e
- extractFromToM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => ix -> ix -> Array r ix e -> m (Array D ix e)
- extractFromTo' :: forall r ix e. (HasCallStack, Index ix, Source r e) => ix -> ix -> Array r ix e -> Array D ix e
- deleteRowsM :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Ix1 -> Sz Ix1 -> Array r ix e -> m (Array DL ix e)
- deleteColumnsM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Ix1 -> Sz Ix1 -> Array r ix e -> m (Array DL ix e)
- deleteRegionM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Dim -> Ix1 -> Sz Ix1 -> Array r ix e -> m (Array DL ix e)
- appendOuterM :: forall ix e m. (Index ix, MonadThrow m) => Array DL ix e -> Array DL ix e -> m (Array DL ix e)
- appendM :: forall r1 r2 ix e m. (MonadThrow m, Index ix, Source r1 e, Source r2 e) => Dim -> Array r1 ix e -> Array r2 ix e -> m (Array DL ix e)
- append' :: forall r1 r2 ix e. (HasCallStack, Index ix, Source r1 e, Source r2 e) => Dim -> Array r1 ix e -> Array r2 ix e -> Array DL ix e
- concatOuterM :: forall ix e m. (Index ix, MonadThrow m) => [Array DL ix e] -> m (Array DL ix e)
- concatM :: forall r ix e f m. (MonadThrow m, Foldable f, Index ix, Source r e) => Dim -> f (Array r ix e) -> m (Array DL ix e)
- concat' :: forall f r ix e. (HasCallStack, Foldable f, Index ix, Source r e) => Dim -> f (Array r ix e) -> Array DL ix e
- stackSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => Dim -> f (Array r (Lower ix) e) -> m (Array DL ix e)
- stackOuterSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => f (Array r (Lower ix) e) -> m (Array DL ix e)
- stackInnerSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => f (Array r (Lower ix) e) -> m (Array DL ix e)
- splitAtM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Dim -> Int -> Array r ix e -> m (Array D ix e, Array D ix e)
- splitAt' :: forall r ix e. (HasCallStack, Index ix, Source r e) => Dim -> Int -> Array r ix e -> (Array D ix e, Array D ix e)
- splitExtractM :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Dim -> Ix1 -> Sz Ix1 -> Array r ix e -> m (Array D ix e, Array D ix e, Array D ix e)
- replaceSlice :: forall r r' ix e m. (MonadThrow m, Source r e, Source r' e, Index ix, Index (Lower ix)) => Dim -> Ix1 -> Array r' (Lower ix) e -> Array r ix e -> m (Array DL ix e)
- replaceOuterSlice :: forall r ix e m. (MonadThrow m, Index ix, Source r e, Load r (Lower ix) e) => Ix1 -> Array r (Lower ix) e -> Array r ix e -> m (Array DL ix e)
- upsample :: forall r ix e. Load r ix e => e -> Stride ix -> Array r ix e -> Array DL ix e
- downsample :: forall r ix e. (Source r e, Load r ix e) => Stride ix -> Array r ix e -> Array DL ix e
- zoom :: forall r ix e. (Index ix, Source r e) => Stride ix -> Array r ix e -> Array DL ix e
- zoomWithGrid :: forall r ix e. (Index ix, Source r e) => e -> Stride ix -> Array r ix e -> Array DL ix e
- transformM :: forall r ix e r' ix' e' a m. (Manifest r e, Index ix, Source r' e', Index ix', 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)
- transform' :: forall ix e r' ix' e' a. (HasCallStack, Source r' e', Index ix', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e
- transform2M :: (Manifest r e, Index ix, Source r1 e1, Source r2 e2, Index ix1, Index ix2, 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)
- transform2' :: (HasCallStack, Source r1 e1, Source r2 e2, Index ix, Index ix1, Index ix2) => (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
- (!>) :: forall r ix e. (HasCallStack, Index ix, Index (Lower ix), Source r e) => Array r ix e -> Int -> Array r (Lower ix) e
- (!?>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Array r ix e -> Int -> m (Array r (Lower ix) e)
- (??>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => m (Array r ix e) -> Int -> m (Array r (Lower ix) e)
- (<!) :: forall r ix e. (HasCallStack, Index ix, Source r e) => Array r ix e -> Int -> Array D (Lower ix) e
- (<!?) :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Array r ix e -> Int -> m (Array D (Lower ix) e)
- (<??) :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => m (Array r ix e) -> Int -> m (Array D (Lower ix) e)
- (<!>) :: forall r ix e. (HasCallStack, Index ix, Index (Lower ix), Source r e) => Array r ix e -> (Dim, Int) -> Array D (Lower ix) e
- (<!?>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Array r ix e -> (Dim, Int) -> m (Array D (Lower ix) e)
- (<??>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => m (Array r ix e) -> (Dim, Int) -> m (Array D (Lower ix) e)
- outerSlices :: forall r ix e. (Index ix, Index (Lower ix), Source r e) => Array r ix e -> Array D Ix1 (Array r (Lower ix) e)
- innerSlices :: forall r ix e. (Index ix, Source r e) => Array r ix e -> Array D Ix1 (Array D (Lower ix) e)
- withinSlices :: forall n r ix e. (IsIndexDimension ix n, Index (Lower ix), Source r e) => Dimension n -> Array r ix e -> Array D Ix1 (Array D (Lower ix) e)
- withinSlicesM :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Dim -> Array r ix e -> m (Array D Ix1 (Array D (Lower ix) e))
- quicksort :: (Manifest r e, Ord e) => Vector r e -> Vector r e
- quicksortBy :: Manifest r e => (e -> e -> Ordering) -> Vector r e -> Vector r e
- quicksortByM :: (Manifest r e, MonadUnliftIO m) => (e -> e -> m Ordering) -> Vector r e -> m (Vector r e)
- tally :: (Manifest r e, Load r ix e, Ord e) => Array r ix e -> Vector DS (e, Int)
- iterateUntil :: (Load r' ix e, Manifest r e, NFData (Array r ix e)) => (Int -> Array r ix e -> Array r ix e -> Bool) -> (Int -> Array r ix e -> Array r' ix e) -> Array r ix e -> Array r ix e
- fromList :: forall r e. Manifest r e => Comp -> [e] -> Vector r e
- fromListsM :: forall r ix e m. (Ragged L ix e, Manifest r e, MonadThrow m) => Comp -> [ListItem ix e] -> m (Array r ix e)
- fromLists' :: forall r ix e. (HasCallStack, Ragged L ix e, Manifest r e) => Comp -> [ListItem ix e] -> Array r ix e
- toList :: (Index ix, Source r e) => Array r ix e -> [e]
- toLists :: (Ragged L ix e, Shape r ix, Source r e) => Array r ix e -> [ListItem ix e]
- toLists2 :: (Source r e, Index ix, Index (Lower ix)) => Array r ix e -> [[e]]
- toLists3 :: (Source r e, Index ix, Index (Lower ix), Index (Lower (Lower ix))) => Array r ix e -> [[[e]]]
- toLists4 :: (Source r e, Index ix, Index (Lower ix), Index (Lower (Lower ix)), Index (Lower (Lower (Lower ix)))) => Array r ix e -> [[[[e]]]]
- module Data.Massiv.Array.Mutable
- module Data.Massiv.Core
- module Data.Massiv.Array.Delayed
- module Data.Massiv.Array.Manifest
- module Data.Massiv.Array.Stencil
- module Data.Massiv.Array.Numeric
Construct
With constant value
empty :: forall r ix e. Load 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
>>>
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
Create an Array with a single element.
Examples
>>>
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 :: Load r ix e => Comp -> Sz ix -> e -> Array r ix e Source #
Construct an array of the specified size that contains the same element in all of the cells.
Since: 0.3.0
With a function
:: Load r ix e | |
=> Comp | |
-> 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 :: Load 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 :: Load 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 U
nboxed type constructor in the below example.
Examples
>>>
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 :: Load 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 :: Load r Ix1 e => r -> Comp -> Sz1 -> (Ix1 -> e) -> Vector r 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
>>>
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
unfoldlS_ :: Index ix => 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 achieve such effect.
Since: 0.3.0
iunfoldlS_ :: forall ix e a. Index ix => 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. Index ix => Sz ix -> (a -> (e, a)) -> a -> Array DL ix e Source #
Right unfold into a delayed load array. For the opposite direction use unfoldlS_
.
Examples
>>>
import Data.Massiv.Array
>>>
unfoldrS_ (Sz1 10) (\xs -> (Prelude.head xs, Prelude.tail xs)) ([10 ..] :: [Int])
Array DL Seq (Sz1 10) [ 10, 11, 12, 13, 14, 15, 16, 17, 18, 19 ]
Since: 0.3.0
iunfoldrS_ :: forall ix e a. Index ix => 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
:: forall ix e g it. (Iterator it, Index ix) | |
=> it | Iterator |
-> g | Initial seed |
-> (g -> (g, g)) | A function that can split a seed into two independent seeds. It will be called the same number of times as the number of jobs that will get scheduled during parallelization. Eg. only once for the sequential case. |
-> Comp | Computation strategy. |
-> Sz ix | Resulting size of the array. |
-> (Ix1 -> ix -> g -> (e, g)) | A function that produces a value and the next seed. It takes both versions of the index, in linear and in multi-dimensional forms, as well as the current seeding value. |
-> Array DL ix e |
Create a delayed array with an initial seed and a splitting function. It is
somewhat similar to iunfoldlS_
function, but it is capable of parallelizing
computation and iterating over the array accoriding to the supplied
Iterator
. Upon parallelization every job will get the second part of the
result produced by the split function, while the first part will be used for
subsequent splits. This function is similar to
generateSplitSeedArray
Since: 1.0.2
Random
:: forall ix e g. (Index ix, RandomGen g, Uniform e) | |
=> g | Initial random value generator. |
-> Comp | Computation strategy. |
-> Sz ix | Resulting size of the array. |
-> Array DL ix e |
Generate a random array where all elements are sampled from a uniform distribution.
Since: 1.0.0
:: forall ix e g. (Index ix, RandomGen g, UniformRange e) | |
=> g | Initial random value generator. |
-> (e, e) | Inclusive range in which values will be generated in. |
-> Comp | Computation strategy. |
-> Sz ix | Resulting size of the array. |
-> Array DL ix e |
Same as uniformArray
, but will generate values in a supplied range.
Since: 1.0.0
:: forall ix e g. Index ix | |
=> g | Initial random value generator |
-> (g -> (g, g)) | A function that can split a generator into two independent generators. It will only be called if supplied computation strategy needs more than one worker threads. |
-> (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 randomArrayWS
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.
Note: Starting with massiv-1.1.0 this function will be deprecated in
favor of a more general genSplitArray
Examples
>>>
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 Random
>>>
gen = Random.mkStdGen 217
>>>
randomArray gen Random.split Random.random (ParN 2) (Sz2 2 3) :: Array DL Ix2 Double
Array DL (ParN 2) (Sz (2 :. 3)) [ [ 0.2616843941380331, 0.600959468331641, 0.4382415961606372 ] , [ 0.27812817813217605, 0.2993277194932741, 0.2774105268603957 ] ]
Since: 1.0.0
:: forall r ix e g. (Manifest r e, Index ix) | |
=> 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
>>>
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.11217260506402493, 0.8870919238985904, 0.2616843941380331 ] , [ 0.600959468331641, 0.4382415961606372, 0.8375162573397977 ] ]
Since: 0.3.4
:: forall r ix e g m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) | |
=> WorkerStates g | Use |
-> 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
In the example below we take a stateful random number generator from wmc-random, which is not thread safe, and safely parallelize it by giving each thread it's own generator. There is a caveat of course, statistical independence will depend on the entropy in your initial seeds, so do not use the example below verbatim, since initial seeds are sequential numbers.
>>>
import Data.Massiv.Array as A
>>>
import System.Random.MWC as MWC (initialize)
>>>
import System.Random.Stateful (uniformRM)
>>>
import Control.Scheduler (initWorkerStates, getWorkerId)
>>>
:set -XTypeApplications
>>>
gens <- initWorkerStates Par (MWC.initialize . A.toPrimitiveVector . A.singleton @P @Ix1 . fromIntegral . getWorkerId)
>>>
randomArrayWS gens (Sz2 2 3) (uniformRM (0, 9)) :: IO (Matrix P Double)
Array P Par (Sz (2 :. 3)) [ [ 8.999240522095299, 6.832223390653755, 3.065728078741671 ] , [ 7.242581103346686, 2.4565807301968623, 0.4514262066689775 ] ]>>>
randomArrayWS gens (Sz1 6) (uniformRM (0, 9)) :: IO (Vector P Int)
Array P Par (Sz1 6) [ 8, 8, 7, 1, 1, 2 ]
Since: 0.3.4
Applicative
makeArrayA :: forall r ix e f. (Manifest r e, Index ix, 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. (Manifest r e, Index ix, 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
makeArrayLinearA :: forall r ix e f. (Manifest r e, Index ix, Applicative f) => Sz ix -> (Int -> f e) -> f (Array r ix e) Source #
Same as makeArrayA
, but with linear index.
Since: 0.4.5
Enumeration
(...) :: Index ix => ix -> ix -> Array D ix ix infix 4 Source #
Handy synonym for
. Similar to rangeInclusive
Seq
..
for list.
>>>
Ix1 4 ... 10
Array D Seq (Sz1 7) [ 4, 5, 6, 7, 8, 9, 10 ]
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
>>>
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
:: forall ix m. (Index ix, MonadThrow m) | |
=> Comp | Computation strategy |
-> ix | Start |
-> ix | Step. Negative and positive values are ok, but can't have zeros |
-> ix | End |
-> m (Array D ix ix) |
Same as range
, but with a custom step.
Throws Exceptions: IndexZeroException
Examples
>>>
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' :: (HasCallStack, Index ix) => Comp -> ix -> ix -> ix -> Array D ix ix Source #
Same as rangeStepM
, but will throw an error whenever step
contains zeros.
Example
>>>
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 rangeStepM
, except the finish index is included.
Since: 0.3.0
rangeStepInclusive' :: (HasCallStack, Index ix) => Comp -> ix -> ix -> ix -> Array D ix ix Source #
Just like range
, except the finish index is included.
Since: 0.3.1
:: Index ix | |
=> Comp | Computation strategy |
-> ix |
|
-> Sz ix |
|
-> 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
:: Index ix | |
=> Comp | Computation strategy |
-> ix |
|
-> ix |
|
-> Sz ix |
|
-> Array D ix ix |
Same as rangeSize
, but with ability to specify the step.
Since: 0.3.0
Same as enumFromStepN
with step dx = 1
.
Related: senumFromN
, senumFromStepN
,
enumFromStepN
, rangeSize
, rangeStepSize
, range
Examples
>>>
import Data.Massiv.Array
>>>
enumFromN Seq (5 :: Double) 3
Array D Seq (Sz1 3) [ 5.0, 6.0, 7.0 ]
Similar:
Prelude.
enumFromTo
- Very similar to
[i .. i + n - 1]
, except thatenumFromN
is faster, but it only works forNum
and not forEnum
elements Data.Vector.Generic.
enumFromN
Since: 0.1.0
:: Num e | |
=> Comp | |
-> e |
|
-> e |
|
-> Sz1 |
|
-> Vector D e |
Enumerate from a starting number x
exactly n
times with a custom step value
dx
. Unlike senumFromStepN
, there is no dependency on neigboring
elements therefore enumFromStepN
is parallelizable.
Related: senumFromN
, senumFromStepN
,
enumFromN
, rangeSize
, rangeStepSize
, range
, rangeStepM
Examples
>>>
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 ]>>>
enumFromStepN Seq (-pi :: Float) (pi/4) 9
Array D Seq (Sz1 9) [ -3.1415927, -2.3561945, -1.5707964, -0.78539824, 0.0, 0.78539824, 1.5707963, 2.3561947, 3.1415927 ]
Similar:
Prelude.
enumFrom
- Similar to
take n [x, x + dx ..]
, except thatenumFromStepN
is parallelizable and it only works forNum
and not forEnum
elements. Floating point value will be slightly different as well. Data.Vector.Generic.
enumFromStepN
- Similar in the outcome, but very different in the way it works.
Since: 0.1.0
Expansion
expandWithin :: forall n ix e r a. (IsIndexDimension ix n, Index (Lower ix), Manifest r 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
or Array
r Ix1
a
. Then
you use Array
r Ix2
aexpandWithin
and a creation function a -> Int -> b
to create an
or Array
D
Ix2
b
respectfully.Array
D
Ix3
b
Examples
>>>
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 :: forall r ix a b m. (Index ix, Index (Lower ix), Manifest r 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' :: forall r ix a b. (HasCallStack, Index ix, Index (Lower ix), Manifest r 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 :: forall r ix a b. (Index ix, Index (Lower ix), Manifest r 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 :: forall r ix a b. (Index ix, Index (Lower ix), Manifest r 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 :: Strategy r => Array r ix e -> Comp Source #
Get computation strategy of this array
Since: 0.1.0
setComp :: Strategy r => Comp -> Array r ix e -> Array r ix e Source #
Set computation strategy for this array
Example
>>>
: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 ]
computeS :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e Source #
Compute array sequentially disregarding predefined computation strategy. Very much
the same as computePrimM
, but executed in ST
, thus pure.
Since: 0.1.0
computeP :: forall r ix e r'. (Manifest r e, Load r' ix e) => Array r' ix e -> Array r ix e Source #
Compute array in parallel using all cores disregarding predefined computation strategy. Computation stategy of the resulting array will match the source, despite that it is diregarded.
Since: 0.5.4
computeIO :: forall r ix e r' m. (Manifest r e, Load r' ix e, MonadIO m) => Array r' ix e -> m (Array r ix e) Source #
computePrimM :: forall r ix e r' m. (Manifest r e, Load r' ix e, PrimMonad m) => Array r' ix e -> m (Array r ix e) Source #
Compute an array in PrimMonad
sequentially disregarding predefined computation
strategy.
Since: 0.4.5
computeAs :: (Manifest r 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
>>>
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 :: (Manifest r 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
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'. (Manifest r e, Source r' e, Index ix) => Array r' ix e -> Array r ix e Source #
computeWithStride :: forall r ix e r'. (Manifest r e, StrideLoad r' ix e) => Stride ix -> Array r' ix e -> Array r ix e Source #
computeWithStrideAs :: (Manifest r 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 :: (Manifest r e, Index ix) => 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'. (Manifest r 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 :: (Manifest r 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
fromRaggedArrayM :: forall r ix e r' m. (Manifest r e, Ragged 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'. (HasCallStack, Manifest r e, Ragged r' ix e) => Array r' ix e -> Array r ix e Source #
Same as fromRaggedArrayM
, but will throw an impure exception if its shape is not
rectangular.
Since: 0.1.1
Vector
module Data.Massiv.Vector
Size
size :: Size r => Array r ix e -> Sz ix Source #
O(1) - Get the exact size of an immutabe array. Most of the time will
produce the size in constant time, except for DS
representation, which could result in evaluation of the whole stream. See
maxLinearSize
and slength
for more info.
Since: 0.1.0
elemsCount :: (Index ix, Size r) => Array r ix e -> Int Source #
O(1) - Get the number of elements in the array.
Examples
>>>
import Data.Massiv.Array
>>>
elemsCount $ range Seq (Ix1 10) 15
5
Since: 0.1.0
isEmpty :: (Index ix, Size r) => Array r ix e -> Bool Source #
O(1) - Check if array has elements.
Examples
>>>
import Data.Massiv.Array
>>>
isEmpty (singleton 1 :: Array D Ix2 Int)
False>>>
isEmpty (empty :: Array D Ix2 Int)
True
Since: 1.0.0
isNotEmpty :: (Index ix, Size r) => Array r ix e -> Bool Source #
O(1) - Check if array has elements.
Examples
>>>
import Data.Massiv.Array
>>>
isNotEmpty (singleton 1 :: Array D Ix2 Int)
True>>>
isNotEmpty (empty :: Array D Ix2 Int)
False
Since: 1.0.0
isNull :: Shape r ix => Array r ix e -> Bool Source #
O(1) - Check whether an array is empty or not.
Examples
>>>
import Data.Massiv.Array
>>>
isNull $ range Seq (Ix2 10 20) (11 :. 21)
False>>>
isNull $ range Seq (Ix2 10 20) (10 :. 21)
True>>>
isNull (empty :: Array D Ix5 Int)
True>>>
isNull $ sfromList []
True
Since: 1.0.0
isNotNull :: Shape r ix => Array r ix e -> Bool Source #
O(1) - Check if array has elements.
Examples
>>>
import Data.Massiv.Array
>>>
isNotNull (singleton 1 :: Array D Ix2 Int)
True>>>
isNotNull (empty :: Array D Ix2 Int)
False
Since: 0.5.1
Indexing
(!?) :: forall r ix e m. (Index ix, Manifest r e, MonadThrow m) => Array r ix e -> ix -> m e infixl 4 Source #
O(1) - Infix version of indexM
.
Exceptions: IndexOutOfBoundsException
Examples
>>>
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
(!) :: forall r ix e. (HasCallStack, Manifest r e, Index ix) => Array r ix e -> ix -> e infixl 4 Source #
O(1) - Infix version of index'
.
Examples
>>>
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
Since: 0.1.0
(??) :: (Index ix, Manifest r 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.
Exceptions: IndexOutOfBoundsException
Examples
>>>
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 U Seq (Sz (1 :. 3)) [ [ 4, 5, 6 ] ] )>>>
ma ??> 1 ?? 0 :. 2
Just 6>>>
ma ?? 1 :> 0 :. 2
Just 6
Since: 0.1.0
index' :: (HasCallStack, Index ix, Manifest r e) => Array r ix e -> ix -> e Source #
O(1) - Lookup an element in the array. This is a partial function and it will throw
an error when index is out of bounds. It is safer to use indexM
instead.
Examples
>>>
import Data.Massiv.Array
>>>
:set -XOverloadedLists
>>>
xs = [0..100] :: Array U Ix1 Int
>>>
index' xs 50
50
Since: 0.1.0
defaultIndex :: (Index ix, Manifest r 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
>>>
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 :: (Index ix, Manifest r 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
>>>
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 :: (Index ix, Source r 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
>>>
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' :: (HasCallStack, Index ix, Source r e) => Array r ix e -> ix -> e Source #
Similar to evaluateM
, but will throw an error on out of bounds indices.
Examples
>>>
import Data.Massiv.Array
>>>
evaluate' (range Seq (Ix2 10 20) (100 :. 210)) 50
60 :. 70
Since: 0.3.0
Mapping
map :: (Index ix, Source r e') => (e' -> e) -> Array r ix e' -> Array D ix e Source #
Map a function over an array
Since: 0.1.0
imap :: forall r ix e a. (Index ix, Source r e) => (ix -> e -> a) -> Array r ix e -> Array D ix a Source #
Map an index aware function over an array
Since: 0.1.0
Traversing
Applicative
traverseA :: forall r ix e r' a f. (Source r' a, Manifest r e, Index ix, 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
instead will always be significantly faster, roughly
about 30 times faster in practice.
Since: 0.2.6
traverseA_ :: forall r ix e a f. (Index ix, Source r 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' a, Manifest r e, Index ix, 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 a, Index ix, 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
sequenceA :: forall r ix e r' f. (Source r' (f e), Manifest r e, Index ix, 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. (Index ix, Source r (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' a, Manifest r b, Index ix, 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' a, Manifest r b, Index ix, 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
Monadic mapping
Sequential
:: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, 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
forM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, 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
imapM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => (ix -> a -> m b) -> Array r' ix a -> m (Array r ix b) Source #
Map an index aware monadic action over an array sequentially.
Since: 0.2.6
iforM :: forall r ix b r' a m. (Source r' a, Manifest r b, Index ix, Monad m) => Array r' ix a -> (ix -> a -> m b) -> m (Array r ix b) Source #
Same as forM
, except with an index aware action.
Since: 0.5.1
mapM_ :: (Source r a, Index ix, Monad m) => (a -> m b) -> Array r ix a -> m () Source #
Map a monadic function over an array sequentially, while discarding the result.
Examples
>>>
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 a, Index ix, Monad m) => Array r ix a -> (a -> m b) -> m () Source #
Just like mapM_
, except with flipped arguments.
Examples
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_ :: (Index ix, Source r 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
>>>
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 a, Index ix, 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. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO m) => (a -> m b) -> Array r' ix a -> m (Array r ix b) Source #
mapWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, 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_ :: forall r ix e a m. (Load r ix e, MonadUnliftIO m) => (e -> m a) -> Array r ix e -> m () Source #
imapIO :: forall r ix b r' a m. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO 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. Respects computation strategy.
Since: 0.2.6
imapWS :: forall r ix b r' a s m. (Source r' a, Manifest r b, Index ix, 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_ :: forall r ix e a m. (Load 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. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO 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' a, Manifest r b, Index ix, 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_ :: (Load r ix e, MonadUnliftIO m) => Array r ix e -> (e -> m a) -> m () Source #
Same as mapIO_
but with arguments flipped.
Example
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. (Size r', Load r' ix a, Manifest r b, MonadUnliftIO 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' a, Manifest r b, Index ix, 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_ :: forall r ix e a m. (Load r ix e, MonadUnliftIO m) => Array r ix e -> (ix -> e -> m a) -> m () Source #
Same as imapIO_
but with arguments flipped.
Since: 0.2.6
imapSchedulerM_ :: (Index ix, Source r e, MonadPrimBase s m) => Scheduler s () -> (ix -> e -> m a) -> Array r ix e -> m () Source #
Same as imapM_
, but will use the supplied scheduler.
Since: 0.3.1
iforSchedulerM_ :: (Index ix, Source r e, MonadPrimBase s m) => Scheduler s () -> Array r ix e -> (ix -> e -> m a) -> m () Source #
Same as imapM_
, but will use the supplied scheduler.
Since: 0.3.1
:: forall r ix e m s. (Load r ix e, MonadPrimBase s m) | |
=> Scheduler s () | |
-> Array r ix e | Array that is being loaded |
-> (Int -> e -> m ()) | Function that writes an element into target array |
-> m () |
iterArrayLinearWithSetM_ Source #
:: forall r ix e m s. (Load r ix e, MonadPrimBase s m) | |
=> Scheduler s () | |
-> Array r ix e | Array that is being loaded |
-> (Int -> e -> m ()) | Function that writes an element into target array |
-> (Ix1 -> Sz1 -> e -> m ()) | Function that efficiently sets a region of an array to the supplied value target array |
-> m () |
iterArrayLinearWithStrideM_ Source #
:: forall r ix e m s. (StrideLoad r ix e, MonadPrimBase s m) | |
=> Scheduler s () | |
-> Stride ix | Stride to use |
-> Sz ix | Size of the target array affected by the stride. |
-> Array r ix e | Array that is being loaded |
-> (Int -> e -> m ()) | Function that writes an element into target array |
-> m () |
Zipping
zip :: (Index ix, Source r1 e1, Source r2 e2) => Array r1 ix e1 -> Array r2 ix e2 -> Array D ix (e1, e2) Source #
Zip two arrays
Since: 0.1.0
zip3 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3) => Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array D ix (e1, e2, e3) Source #
Zip three arrays
Since: 0.1.0
zip4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix (e1, e2, e3, e4) Source #
Zip four arrays
Since: 0.5.4
unzip :: (Index ix, Source r (e1, e2)) => Array r ix (e1, e2) -> (Array D ix e1, Array D ix e2) Source #
Unzip two arrays
Since: 0.1.0
unzip3 :: (Index ix, Source r (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
Since: 0.1.0
unzip4 :: (Index ix, Source r (e1, e2, e3, e4)) => Array r ix (e1, e2, e3, e4) -> (Array D ix e1, Array D ix e2, Array D ix e3, Array D ix e4) Source #
Unzip four arrays
Since: 0.5.4
zipWith :: (Index ix, Source r1 e1, Source r2 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 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 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.
zipWith4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => (e1 -> e2 -> e3 -> e4 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix e Source #
Just like zipWith
, except zip four arrays with a function.
Since: 0.5.4
izipWith :: (Index ix, Source r1 e1, Source r2 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 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 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.
izipWith4 :: (Index ix, Source r1 e1, Source r2 e2, Source r3 e3, Source r4 e4) => (ix -> e1 -> e2 -> e3 -> e4 -> e) -> Array r1 ix e1 -> Array r2 ix e2 -> Array r3 ix e3 -> Array r4 ix e4 -> Array D ix e Source #
Just like zipWith4
, except with an index aware function.
Since: 0.5.4
Applicative
zipWithA :: (Source r1 e1, Source r2 e2, Applicative f, Manifest r e, Index 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 sequentially and using the Applicative
. Note that
resulting array has Manifest representation.
Since: 0.3.0
izipWithA :: (Source r1 e1, Source r2 e2, Applicative f, Manifest r e, Index ix) => (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 sequentially and using the Applicative
. Note that
resulting array has Manifest representation.
Since: 0.3.0
zipWith3A :: (Source r1 e1, Source r2 e2, Source r3 e3, Applicative f, Manifest r e, Index 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 zipWithA
, but for three arrays.
Since: 0.3.0
izipWith3A :: (Source r1 e1, Source r2 e2, Source r3 e3, Applicative f, Manifest r e, Index ix) => (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
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
Comp
utation strategy setting.
O(n) - Unstructured fold of an array.
Since: 0.3.0
:: (Index ix, Source r e, Monoid m) | |
=> (ix -> e -> m) | Convert each element of an array to an appropriate |
-> 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
:: (Index ix, Source r e, Semigroup m) | |
=> (ix -> e -> m) | Convert each element of an array to an appropriate |
-> m | Initial element that must be neutral to the ( |
-> Array r ix e | Source array |
-> m |
O(n) - Semigroup fold over an array with an index aware function.
Since: 0.2.4
:: (Index ix, Source r e, Semigroup m) | |
=> (e -> m) | Convert each element of an array to an appropriate |
-> m | Initial element that must be neutral to the ( |
-> Array r ix e | Source array |
-> m |
O(n) - Semigroup fold over an array.
Since: 0.1.6
foldOuterSlice :: (Index ix, Index (Lower ix), Source r e, Monoid m) => (Array r (Lower ix) e -> m) -> Array r ix e -> m Source #
Reduce each outer slice into a monoid and mappend results together
Example
>>>
import Data.Massiv.Array as A
>>>
import Data.Monoid (Product(..))
>>>
arr = computeAs P $ iterateN (Sz2 2 3) (+1) (10 :: Int)
>>>
arr
Array P Seq (Sz (2 :. 3)) [ [ 11, 12, 13 ] , [ 14, 15, 16 ] ]>>>
getProduct $ foldOuterSlice (\row -> Product (A.sum row)) arr
1620>>>
(11 + 12 + 13) * (14 + 15 + 16) :: Int
1620
Since: 0.4.3
ifoldOuterSlice :: (Index ix, Index (Lower ix), Source r e, Monoid m) => (Ix1 -> Array r (Lower ix) e -> m) -> Array r ix e -> m Source #
Reduce each outer slice into a monoid with an index aware function and mappend results together
Since: 0.4.3
foldInnerSlice :: (Source r e, Index ix, Monoid m) => (Array D (Lower ix) e -> m) -> Array r ix e -> m Source #
Reduce each inner slice into a monoid and mappend results together
Example
>>>
import Data.Massiv.Array as A
>>>
import Data.Monoid (Product(..))
>>>
arr = computeAs P $ iterateN (Sz2 2 3) (+1) (10 :: Int)
>>>
arr
Array P Seq (Sz (2 :. 3)) [ [ 11, 12, 13 ] , [ 14, 15, 16 ] ]>>>
getProduct $ foldInnerSlice (\column -> Product (A.sum column)) arr
19575>>>
(11 + 14) * (12 + 15) * (13 + 16) :: Int
19575
Since: 0.4.3
ifoldInnerSlice :: (Source r e, Index ix, Monoid m) => (Ix1 -> Array D (Lower ix) e -> m) -> Array r ix e -> m Source #
Reduce each inner slice into a monoid with an index aware function and mappend results together
Since: 0.4.3
minimumM :: (MonadThrow m, Shape r ix, Source r e, Ord e) => Array r ix e -> m e Source #
O(n) - Compute minimum of all elements.
Since: 0.3.0
minimum' :: forall r ix e. (HasCallStack, Shape r ix, Source r e, Ord e) => Array r ix e -> e Source #
O(n) - Compute minimum of all elements.
Since: 0.3.0
maximumM :: (MonadThrow m, Shape r ix, Source r e, Ord e) => Array r ix e -> m e Source #
O(n) - Compute maximum of all elements.
Since: 0.3.0
maximum' :: forall r ix e. (HasCallStack, Shape r ix, Source r e, Ord e) => Array r ix e -> e Source #
O(n) - Compute maximum of all elements.
Since: 0.3.0
sum :: (Index ix, Source r e, Num e) => Array r ix e -> e Source #
O(n) - Compute sum of all elements.
Since: 0.1.0
product :: (Index ix, Source r e, Num e) => Array r ix e -> e Source #
O(n) - Compute product of all elements.
Since: 0.1.0
and :: (Index ix, Source r Bool) => Array r ix Bool -> Bool Source #
O(n) - Compute conjunction of all elements.
Since: 0.1.0
or :: (Index ix, Source r Bool) => Array r ix Bool -> Bool Source #
O(n) - Compute disjunction of all elements.
Since: 0.1.0
all :: (Index ix, Source r e) => (e -> Bool) -> Array r ix e -> Bool Source #
O(n) - Determines whether all elements of the array satisfy a predicate.
Since: 0.1.0
any :: (Index ix, Source r e) => (e -> Bool) -> Array r ix e -> Bool Source #
O(n) - Determines whether any element of the array satisfies a predicate.
Since: 0.1.0
elem :: (Eq e, Index ix, Source r e) => e -> Array r ix e -> Bool Source #
O(n) - Determines whether an element is present in the array.
Since: 0.5.5
eqArrays :: (Index ix, Source r1 e1, Source r2 e2) => (e1 -> e2 -> Bool) -> Array r1 ix e1 -> Array r2 ix e2 -> Bool Source #
Compute array equality by applying a comparing function to each element. Empty arrays are always equal, regardless of their size.
Since: 0.5.7
compareArrays :: (Index ix, Source r1 e1, Source r2 e2) => (e1 -> e2 -> Ordering) -> Array r1 ix e1 -> Array r2 ix e2 -> Ordering Source #
Compute array ordering by applying a comparing function to each element. The exact ordering is unspecified so this is only intended for use in maps and the like where you need an ordering but do not care about which one is used.
Since: 0.5.7
Single dimension folds
Safe inner most
ifoldlInner :: (Index (Lower ix), Index ix, Source r 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), Index ix, Source r 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), Index ix, Source r 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), Index ix, Source r 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
foldInner :: (Monoid e, Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D (Lower ix) e Source #
Monoidal fold over the inner most dimension.
Since: 0.4.3
Type safe within
ifoldlWithin :: (Index (Lower ix), IsIndexDimension ix n, Source r 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 e) => Dimension n -> (a -> e -> a) -> a -> Array r ix e -> Array D (Lower ix) a Source #
Left fold along a specified dimension.
Example
>>>
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 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 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
foldWithin :: (Source r a, Monoid a, Index (Lower ix), IsIndexDimension ix n) => Dimension n -> Array r ix a -> Array D (Lower ix) a Source #
Monoidal fold over some internal dimension.
Since: 0.4.3
Partial within
ifoldlWithin' :: (HasCallStack, Index (Lower ix), Index ix, Source r 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' :: (HasCallStack, Index (Lower ix), Index ix, Source r 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' :: (HasCallStack, Index (Lower ix), Index ix, Source r 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' :: (HasCallStack, Index (Lower ix), Index ix, Source r 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
foldWithin' :: (HasCallStack, Index ix, Source r a, Monoid a, Index (Lower ix)) => Dim -> Array r ix a -> Array D (Lower ix) a Source #
Monoidal fold over some internal dimension. This is a pratial function and will
result in IndexDimensionException
if supplied dimension is invalid.
Since: 0.4.3
Sequential folds
Functions in this section will fold any Source
array sequentially, regardless of the inner
Comp
utation strategy setting.
foldlS :: (Index ix, Source r e) => (a -> e -> a) -> a -> Array r ix e -> a Source #
O(n) - Left fold, computed sequentially.
Since: 0.1.0
foldrS :: (Index ix, Source r e) => (e -> a -> a) -> a -> Array r ix e -> a Source #
O(n) - Right fold, computed sequentially.
Since: 0.1.0
ifoldlS :: (Index ix, Source r 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 :: (Index ix, Source r 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 :: (Index ix, Source r 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 :: (Index ix, Source r 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_ :: (Index ix, Source r 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_ :: (Index ix, Source r 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 :: (Index ix, Source r 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 :: (Index ix, Source r 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_ :: (Index ix, Source r 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_ :: (Index ix, Source r 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 :: (Index ix, Source r 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 :: (Index ix, Source r 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 :: (Index ix, Source r 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 Comp
utation 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.
:: (MonadIO m, Index ix, Source r e) | |
=> (a -> e -> a) | Folding function |
-> a | Accumulator. Will be applied to |
-> (b -> a -> b) | Chunk results folding function |
-> 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
>>>
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, Index ix, Source r 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
>>>
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, Index ix, Source r 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, Index ix, Source r 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
:: (MonadUnliftIO m, Index ix, Source r 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, Index ix, Source r 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 :: forall r e. Source r e => Matrix r e -> Matrix D e Source #
Transpose a 2-dimensional array
Examples
>>>
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 :: forall r ix e. (Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D ix e Source #
Transpose inner two dimensions of at least rank-2 array.
Examples
>>>
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 :: forall r ix e. (Index (Lower ix), Index ix, Source r e) => Array r ix e -> Array D ix e Source #
Transpose outer two dimensions of at least rank-2 array.
Examples
>>>
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 :: forall n r ix e. (IsIndexDimension ix n, Index ix, Source r 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
>>>
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' :: forall r ix e. (HasCallStack, Index ix, Source r 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 :: forall r ix e m. (MonadThrow m, Index ix, Source r 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
:: forall r ix e r' ix' m. (Manifest r e, Index ix, Source r' e, Index ix', 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
>>>
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
:: forall r ix ix' e. (HasCallStack, Source r e, Index ix, 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 :: forall r ix ix' e m. (MonadThrow m, Index ix', Index ix, Size r) => Sz ix' -> Array r ix e -> m (Array r ix' e) Source #
O(1) - Change the size of an array. Throws
SizeElementsMismatchException
if total number of elements does not match
the supplied array.
Since: 0.3.0
resize' :: forall r ix ix' e. (HasCallStack, Index ix', Index ix, Size r) => 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 :: forall r ix e. (Index ix, Size r) => Array r ix e -> Vector r e Source #
O(1) - Reduce a multi-dimensional array into a flat vector
Since: 0.3.1
Extract
:: forall r ix e m. (MonadThrow m, Index ix, Source r e) | |
=> ix | Starting index |
-> Sz ix | Size of the resulting array |
-> Array r ix e | Source array |
-> m (Array D 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.
Examples
>>>
import Data.Massiv.Array as A
>>>
m <- resizeM (Sz (3 :. 3)) $ Ix1 1 ... 9
>>>
m
Array D Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]>>>
extractM (0 :. 1) (Sz (2 :. 2)) m
Array D Seq (Sz (2 :. 2)) [ [ 2, 3 ] , [ 5, 6 ] ]>>>
a <- resizeM (Sz (3 :> 2 :. 4)) $ Ix1 11 ... 34
>>>
a
Array D Seq (Sz (3 :> 2 :. 4)) [ [ [ 11, 12, 13, 14 ] , [ 15, 16, 17, 18 ] ] , [ [ 19, 20, 21, 22 ] , [ 23, 24, 25, 26 ] ] , [ [ 27, 28, 29, 30 ] , [ 31, 32, 33, 34 ] ] ]>>>
extractM (0 :> 1 :. 1) (Sz (3 :> 1 :. 2)) a
Array D Seq (Sz (3 :> 1 :. 2)) [ [ [ 16, 17 ] ] , [ [ 24, 25 ] ] , [ [ 32, 33 ] ] ]
Since: 0.3.0
:: forall r ix e. (HasCallStack, Index ix, Source r e) | |
=> ix | Starting index |
-> Sz ix | Size of the resulting array |
-> Array r ix e | Source array |
-> Array D ix e |
Same as extractM
, but will throw a runtime exception from pure code if supplied dimensions
are incorrect.
Since: 0.1.0
:: forall r ix e m. (MonadThrow m, Index ix, Source r e) | |
=> ix | Starting index |
-> ix | Index up to which elements should be extracted. |
-> Array r ix e | Source array. |
-> m (Array D ix e) |
Similar to extractM
, except it takes starting and ending index. Result array will not include
the ending index.
Examples
>>>
a <- resizeM (Sz (3 :> 2 :. 4)) $ Ix1 11 ... 34
>>>
a
Array D Seq (Sz (3 :> 2 :. 4)) [ [ [ 11, 12, 13, 14 ] , [ 15, 16, 17, 18 ] ] , [ [ 19, 20, 21, 22 ] , [ 23, 24, 25, 26 ] ] , [ [ 27, 28, 29, 30 ] , [ 31, 32, 33, 34 ] ] ]>>>
extractFromToM (1 :> 0 :. 1) (3 :> 2 :. 4) a
Array D Seq (Sz (2 :> 2 :. 3)) [ [ [ 20, 21, 22 ] , [ 24, 25, 26 ] ] , [ [ 28, 29, 30 ] , [ 32, 33, 34 ] ] ]
Since: 0.3.0
:: forall r ix e. (HasCallStack, Index ix, Source r e) | |
=> ix | Starting index |
-> ix | Index up to which elmenets should be extracted. |
-> Array r ix e | Source array. |
-> Array D ix e |
Same as extractFromToM
, but throws an error on invalid indices.
Since: 0.2.4
deleteRowsM :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => 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
>>>
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 :: forall r ix e m. (MonadThrow m, Index ix, Source r 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
>>>
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
:: forall r ix e m. (MonadThrow m, Index ix, Source r 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
>>>
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
appendOuterM :: forall ix e m. (Index ix, MonadThrow m) => Array DL ix e -> Array DL ix e -> m (Array DL ix e) Source #
Append two arrays together along the outer most dimension. Inner dimensions must
agree, otherwise SizeMismatchException
.
Since: 0.4.4
appendM :: forall r1 r2 ix e m. (MonadThrow m, Index ix, Source r1 e, Source r2 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
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' :: forall r1 r2 ix e. (HasCallStack, Index ix, Source r1 e, Source r2 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
concatOuterM :: forall ix e m. (Index ix, MonadThrow m) => [Array DL ix e] -> m (Array DL ix e) Source #
Concat arrays together along the outer most dimension. Inner dimensions must agree
for all arrays in the list, otherwise SizeMismatchException
.
Since: 0.4.4
concatM :: forall r ix e f m. (MonadThrow m, Foldable f, Index ix, Source r 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.
Exceptions: IndexDimensionException
, SizeMismatchException
Since: 0.3.0
concat' :: forall f r ix e. (HasCallStack, Foldable f, Index ix, Source r e) => Dim -> f (Array r ix e) -> Array DL ix e Source #
Concat many arrays together along some dimension.
Since: 0.3.0
stackSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => Dim -> f (Array r (Lower ix) e) -> m (Array DL ix e) Source #
Stack slices on top of each other along the specified dimension.
Exceptions: IndexDimensionException
, SizeMismatchException
Examples
Here are the three different ways to stack up two 2D Matrix pages into a 3D array.
>>>
import Data.Massiv.Array as A
>>>
x = compute (iterateN 3 succ 0) :: Matrix P Int
>>>
y = compute (iterateN 3 succ 9) :: Matrix P Int
>>>
x
Array P Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]>>>
y
Array P Seq (Sz (3 :. 3)) [ [ 10, 11, 12 ] , [ 13, 14, 15 ] , [ 16, 17, 18 ] ]>>>
stackSlicesM 1 [x, y] :: IO (Array DL Ix3 Int)
Array DL Seq (Sz (3 :> 3 :. 2)) [ [ [ 1, 10 ] , [ 2, 11 ] , [ 3, 12 ] ] , [ [ 4, 13 ] , [ 5, 14 ] , [ 6, 15 ] ] , [ [ 7, 16 ] , [ 8, 17 ] , [ 9, 18 ] ] ]>>>
stackSlicesM 2 [x, y] :: IO (Array DL Ix3 Int)
Array DL Seq (Sz (3 :> 2 :. 3)) [ [ [ 1, 2, 3 ] , [ 10, 11, 12 ] ] , [ [ 4, 5, 6 ] , [ 13, 14, 15 ] ] , [ [ 7, 8, 9 ] , [ 16, 17, 18 ] ] ]>>>
stackSlicesM 3 [x, y] :: IO (Array DL Ix3 Int)
Array DL Seq (Sz (2 :> 3 :. 3)) [ [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ] , [ [ 10, 11, 12 ] , [ 13, 14, 15 ] , [ 16, 17, 18 ] ] ]
Since: 0.5.4
stackOuterSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => f (Array r (Lower ix) e) -> m (Array DL ix e) Source #
Specialized stackSlicesM
to handling stacking from the outside. It is the inverse of
outerSlices
.
Exceptions: SizeMismatchException
Examples
In this example we stack vectors as row of a matrix from top to bottom:
>>>
import Data.Massiv.Array as A
>>>
x = compute (iterateN 3 succ 0) :: Matrix P Int
>>>
x
Array P Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]>>>
rows = outerSlices x
>>>
A.mapM_ print rows
Array P Seq (Sz1 3) [ 1, 2, 3 ] Array P Seq (Sz1 3) [ 4, 5, 6 ] Array P Seq (Sz1 3) [ 7, 8, 9 ]>>>
stackOuterSlicesM rows :: IO (Matrix DL Int)
Array DL Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]
Since: 0.5.4
stackInnerSlicesM :: forall r ix e f m. (Foldable f, MonadThrow m, Index (Lower ix), Source r e, Index ix) => f (Array r (Lower ix) e) -> m (Array DL ix e) Source #
Specialized stackSlicesM
to handling stacking from the inside. It is the inverse of
innerSlices
.
Exceptions: SizeMismatchException
Examples
In this example we stack vectors as columns of a matrix from left to right:
>>>
import Data.Massiv.Array as A
>>>
x = compute (iterateN 3 succ 0) :: Matrix P Int
>>>
x
Array P Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]>>>
columns = innerSlices x
>>>
A.mapM_ print columns
Array D Seq (Sz1 3) [ 1, 4, 7 ] Array D Seq (Sz1 3) [ 2, 5, 8 ] Array D Seq (Sz1 3) [ 3, 6, 9 ]>>>
stackInnerSlicesM columns :: IO (Matrix DL Int)
Array DL Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]
Since: 0.5.4
:: forall r ix e m. (MonadThrow m, Index ix, Source r e) | |
=> Dim | Dimension along which to split |
-> Int | Index along the dimension to split at |
-> Array r ix e | Source array |
-> m (Array D ix e, Array D ix e) |
O(1) - Split an array into two at an index along a specified dimension.
Related: splitAt'
, splitExtractM
, sliceAt'
, sliceAtM
Exceptions: IndexDimensionException
, SizeSubregionException
Since: 0.3.0
splitAt' :: forall r ix e. (HasCallStack, Index ix, Source r e) => Dim -> Int -> Array r ix e -> (Array D ix e, Array D ix e) Source #
O(1) - Split an array into two at an index along a specified dimension. Throws an error for a wrong dimension or incorrect indices.
Related: splitAtM
, splitExtractM
, sliceAt'
, sliceAtM
Examples
Since: 0.1.0
:: forall r ix e m. (MonadThrow m, Index ix, Source r 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 D ix e, Array D ix e, Array D ix e) |
Split an array in three parts across some dimension
Since: 0.3.5
replaceSlice :: forall r r' ix e m. (MonadThrow m, Source r e, Source r' e, Index ix, Index (Lower ix)) => Dim -> Ix1 -> Array r' (Lower ix) e -> Array r ix e -> m (Array DL ix e) Source #
Replace a slice of an array with another one
Example
>>>
import Data.Massiv.Array
>>>
arr = makeArrayR U Seq (Sz3 3 4 5) fromIx3
>>>
arr' = makeArrayR U Seq (Sz3 3 4 5) (fromIx3 . liftIndex (* 100))
>>>
replaceSlice 2 1 (arr' <!> (2, 3)) arr
Array DL Seq (Sz (3 :> 4 :. 5)) [ [ [ (0,0,0), (0,0,1), (0,0,2), (0,0,3), (0,0,4) ] , [ (0,300,0), (0,300,100), (0,300,200), (0,300,300), (0,300,400) ] , [ (0,2,0), (0,2,1), (0,2,2), (0,2,3), (0,2,4) ] , [ (0,3,0), (0,3,1), (0,3,2), (0,3,3), (0,3,4) ] ] , [ [ (1,0,0), (1,0,1), (1,0,2), (1,0,3), (1,0,4) ] , [ (100,300,0), (100,300,100), (100,300,200), (100,300,300), (100,300,400) ] , [ (1,2,0), (1,2,1), (1,2,2), (1,2,3), (1,2,4) ] , [ (1,3,0), (1,3,1), (1,3,2), (1,3,3), (1,3,4) ] ] , [ [ (2,0,0), (2,0,1), (2,0,2), (2,0,3), (2,0,4) ] , [ (200,300,0), (200,300,100), (200,300,200), (200,300,300), (200,300,400) ] , [ (2,2,0), (2,2,1), (2,2,2), (2,2,3), (2,2,4) ] , [ (2,3,0), (2,3,1), (2,3,2), (2,3,3), (2,3,4) ] ] ]
Since: 0.6.1
replaceOuterSlice :: forall r ix e m. (MonadThrow m, Index ix, Source r e, Load r (Lower ix) e) => Ix1 -> Array r (Lower ix) e -> Array r ix e -> m (Array DL ix e) Source #
Replace an outer slice of an array with another one
Example
>>>
import Data.Massiv.Array
>>>
arr = makeArrayR U Seq (Sz3 3 4 5) fromIx3
>>>
arr' = makeArrayR U Seq (Sz3 3 4 5) (fromIx3 . liftIndex (* 100))
>>>
replaceOuterSlice 1 (arr' !> 2) arr
Array DL Seq (Sz (3 :> 4 :. 5)) [ [ [ (0,0,0), (0,0,1), (0,0,2), (0,0,3), (0,0,4) ] , [ (0,1,0), (0,1,1), (0,1,2), (0,1,3), (0,1,4) ] , [ (0,2,0), (0,2,1), (0,2,2), (0,2,3), (0,2,4) ] , [ (0,3,0), (0,3,1), (0,3,2), (0,3,3), (0,3,4) ] ] , [ [ (200,0,0), (200,0,100), (200,0,200), (200,0,300), (200,0,400) ] , [ (200,100,0), (200,100,100), (200,100,200), (200,100,300), (200,100,400) ] , [ (200,200,0), (200,200,100), (200,200,200), (200,200,300), (200,200,400) ] , [ (200,300,0), (200,300,100), (200,300,200), (200,300,300), (200,300,400) ] ] , [ [ (2,0,0), (2,0,1), (2,0,2), (2,0,3), (2,0,4) ] , [ (2,1,0), (2,1,1), (2,1,2), (2,1,3), (2,1,4) ] , [ (2,2,0), (2,2,1), (2,2,2), (2,2,3), (2,2,4) ] , [ (2,3,0), (2,3,1), (2,3,2), (2,3,3), (2,3,4) ] ] ]
Since: 0.6.1
Upsample/Downsample
:: forall r ix e. Load r ix e | |
=> e | Element to use for filling the newly added cells |
-> Stride ix | Fill cells according to this stride |
-> Array r ix e | Array that will have cells added to |
-> Array DL ix e |
Insert the same element into a Load
able array according to the supplied stride.
Examples
>>>
import Data.Massiv.Array as A
>>>
arr = iterateN (Sz2 3 2) succ (0 :: Int)
>>>
arr
Array DL Seq (Sz (3 :. 2)) [ [ 1, 2 ] , [ 3, 4 ] , [ 5, 6 ] ]>>>
upsample 0 (Stride (2 :. 3)) arr
Array DL Seq (Sz (6 :. 6)) [ [ 1, 0, 0, 2, 0, 0 ] , [ 0, 0, 0, 0, 0, 0 ] , [ 3, 0, 0, 4, 0, 0 ] , [ 0, 0, 0, 0, 0, 0 ] , [ 5, 0, 0, 6, 0, 0 ] , [ 0, 0, 0, 0, 0, 0 ] ]>>>
upsample 9 (Stride (1 :. 2)) arr
Array DL Seq (Sz (3 :. 4)) [ [ 1, 9, 2, 9 ] , [ 3, 9, 4, 9 ] , [ 5, 9, 6, 9 ] ]
Since: 0.3.0
downsample :: forall r ix e. (Source r e, Load 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
:: forall r ix e. (Index ix, Source r e) | |
=> Stride ix | Scaling factor |
-> Array r ix e | Source array |
-> Array DL ix e |
Increaze the size of the array accoridng to the stride multiplier while replicating
the same element to fill the neighbors. It is exactly the same as zoomWithGrid
, but
without the grid.
Example
>>>
import Data.Massiv.Array as A
>>>
arr = resize' (Sz3 1 3 2) (Ix1 1 ... 6)
>>>
arr
Array D Seq (Sz (1 :> 3 :. 2)) [ [ [ 1, 2 ] , [ 3, 4 ] , [ 5, 6 ] ] ]>>>
zoom (Stride (2 :> 2 :. 3)) arr
Array DL Seq (Sz (2 :> 6 :. 6)) [ [ [ 1, 1, 1, 2, 2, 2 ] , [ 1, 1, 1, 2, 2, 2 ] , [ 3, 3, 3, 4, 4, 4 ] , [ 3, 3, 3, 4, 4, 4 ] , [ 5, 5, 5, 6, 6, 6 ] , [ 5, 5, 5, 6, 6, 6 ] ] , [ [ 1, 1, 1, 2, 2, 2 ] , [ 1, 1, 1, 2, 2, 2 ] , [ 3, 3, 3, 4, 4, 4 ] , [ 3, 3, 3, 4, 4, 4 ] , [ 5, 5, 5, 6, 6, 6 ] , [ 5, 5, 5, 6, 6, 6 ] ] ]
Since: 0.4.4
:: forall r ix e. (Index ix, Source r 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
>>>
import Data.Massiv.Array as A
>>>
arr = resize' (Sz2 3 2) (Ix1 1 ... 6)
>>>
arr
Array D Seq (Sz (3 :. 2)) [ [ 1, 2 ] , [ 3, 4 ] , [ 5, 6 ] ]>>>
zoomWithGrid 0 (Stride (2 :. 3)) arr
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. (Manifest r e, Index ix, Source r' e', Index ix', 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' :: forall ix e r' ix' e' a. (HasCallStack, Source r' e', Index ix', 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 :: (Manifest r e, Index ix, Source r1 e1, Source r2 e2, Index ix1, Index ix2, 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' :: (HasCallStack, Source r1 e1, Source r2 e2, Index ix, Index ix1, Index ix2) => (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
(!>) :: forall r ix e. (HasCallStack, Index ix, Index (Lower ix), Source r e) => Array r ix e -> Int -> Array r (Lower 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
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 U 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:
>>>
arr !> 2 !> 0 ! 3
(2,0,3)>>>
evaluateM (arr !> 2 <! 3) 0
(2,0,3)>>>
(arr !> 2 !> 0 ! 3) == (arr ! 2 :> 0 :. 3)
True
Since: 0.1.0
(!?>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Array r ix e -> Int -> m (Array r (Lower ix) e) infixl 4 Source #
(??>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => m (Array r ix e) -> Int -> m (Array r (Lower 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
>>>
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
(<!) :: forall r ix e. (HasCallStack, Index ix, Source r e) => Array r ix e -> Int -> Array D (Lower ix) e infixl 4 Source #
O(1) - Similarly to (!>
) slice an array from an opposite direction.
Since: 0.1.0
(<!?) :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => Array r ix e -> Int -> m (Array D (Lower ix) e) infixl 4 Source #
O(1) - Safe slice from the inside
Since: 0.1.0
(<??) :: forall r ix e m. (MonadThrow m, Index ix, Source r e) => m (Array r ix e) -> Int -> m (Array D (Lower ix) e) infixl 4 Source #
O(1) - Safe slicing continuation from the inside
Since: 0.1.0
From within
(<!>) :: forall r ix e. (HasCallStack, Index ix, Index (Lower ix), Source r e) => Array r ix e -> (Dim, Int) -> Array D (Lower 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
(<!?>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Array r ix e -> (Dim, Int) -> m (Array D (Lower ix) e) infixl 4 Source #
(<??>) :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => m (Array r ix e) -> (Dim, Int) -> m (Array D (Lower ix) e) infixl 4 Source #
O(1) - Safe slicing continuation from within.
Since: 0.1.0
Many slices
outerSlices :: forall r ix e. (Index ix, Index (Lower ix), Source r e) => Array r ix e -> Array D Ix1 (Array r (Lower ix) e) Source #
Create a delayed array of outer slices.
Examples
>>>
import Data.Massiv.Array as A
>>>
A.mapM_ print $ outerSlices (0 ..: (3 :. 2))
Array D Seq (Sz1 2) [ 0 :. 0, 0 :. 1 ] Array D Seq (Sz1 2) [ 1 :. 0, 1 :. 1 ] Array D Seq (Sz1 2) [ 2 :. 0, 2 :. 1 ]
Since: 0.5.4
innerSlices :: forall r ix e. (Index ix, Source r e) => Array r ix e -> Array D Ix1 (Array D (Lower ix) e) Source #
Create a delayed array of inner slices.
Examples
>>>
import Data.Massiv.Array as A
>>>
A.mapM_ print $ innerSlices (0 ..: (3 :. 2))
Array D Seq (Sz1 3) [ 0 :. 0, 1 :. 0, 2 :. 0 ] Array D Seq (Sz1 3) [ 0 :. 1, 1 :. 1, 2 :. 1 ]
Since: 0.5.4
withinSlices :: forall n r ix e. (IsIndexDimension ix n, Index (Lower ix), Source r e) => Dimension n -> Array r ix e -> Array D Ix1 (Array D (Lower ix) e) Source #
Create a delayed array of slices from within. Checks dimension at compile time.
Examples
>>>
import Data.Massiv.Array as A
>>>
arr = fromIx3 <$> (0 ..: (4 :> 3 :. 2))
>>>
print arr
Array D Seq (Sz (4 :> 3 :. 2)) [ [ [ (0,0,0), (0,0,1) ] , [ (0,1,0), (0,1,1) ] , [ (0,2,0), (0,2,1) ] ] , [ [ (1,0,0), (1,0,1) ] , [ (1,1,0), (1,1,1) ] , [ (1,2,0), (1,2,1) ] ] , [ [ (2,0,0), (2,0,1) ] , [ (2,1,0), (2,1,1) ] , [ (2,2,0), (2,2,1) ] ] , [ [ (3,0,0), (3,0,1) ] , [ (3,1,0), (3,1,1) ] , [ (3,2,0), (3,2,1) ] ] ]>>>
A.mapM_ print $ withinSlices Dim2 arr
Array D Seq (Sz (4 :. 2)) [ [ (0,0,0), (0,0,1) ] , [ (1,0,0), (1,0,1) ] , [ (2,0,0), (2,0,1) ] , [ (3,0,0), (3,0,1) ] ] Array D Seq (Sz (4 :. 2)) [ [ (0,1,0), (0,1,1) ] , [ (1,1,0), (1,1,1) ] , [ (2,1,0), (2,1,1) ] , [ (3,1,0), (3,1,1) ] ] Array D Seq (Sz (4 :. 2)) [ [ (0,2,0), (0,2,1) ] , [ (1,2,0), (1,2,1) ] , [ (2,2,0), (2,2,1) ] , [ (3,2,0), (3,2,1) ] ]
Since: 0.5.4
withinSlicesM :: forall r ix e m. (MonadThrow m, Index ix, Index (Lower ix), Source r e) => Dim -> Array r ix e -> m (Array D Ix1 (Array D (Lower ix) e)) Source #
Create a delayed array of slices from within. Same as withinSlices
, but throws an
error on invalid dimension.
Throws Exceptions: IndexDimensionException
Since: 0.5.4
Algorithms
Sorting
quicksort :: (Manifest r e, Ord e) => Vector r e -> Vector r e Source #
This is an implementation of Quicksort, which is an efficient, but unstable sort. This implementation 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
quicksortBy :: Manifest r e => (e -> e -> Ordering) -> Vector r e -> Vector r e Source #
Same as quicksortBy
, but instead of Ord
constraint expects a custom Ordering
.
Since: 0.6.1
quicksortByM :: (Manifest r e, MonadUnliftIO m) => (e -> e -> m Ordering) -> Vector r e -> m (Vector r e) Source #
Same as quicksortBy
, but instead of Ord
constraint expects a custom Ordering
.
Since: 0.6.1
tally :: (Manifest r e, Load r ix e, Ord e) => Array r ix e -> Vector DS (e, Int) Source #
Count number of occurrences of each element in the array. Results will be sorted in ascending order of the element.
Example
>>>
import Data.Massiv.Array as A
>>>
xs = fromList Seq [2, 4, 3, 2, 4, 5, 2, 1] :: Array P Ix1 Int
>>>
xs
Array P Seq (Sz1 8) [ 2, 4, 3, 2, 4, 5, 2, 1 ]>>>
tally xs
Array DS Seq (Sz1 5) [ (1,1), (2,3), (3,1), (4,2), (5,1) ]
Since: 0.4.4
Iterations
:: (Load r' ix e, Manifest r e, NFData (Array 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
>>>
import Data.Massiv.Array
>>>
let arr = computeAs P $ makeLoadArrayS (Sz2 8 8) (0 :: Int) $ \ w -> () <$ w (0 :. 0) 1
>>>
arr
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 ] ]>>>
let nextPascalRow cur above = if cur == 0 then above else cur
>>>
let 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) arr
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
Convert a flat list into a vector
Since: 0.1.0
fromListsM :: forall r ix e m. (Ragged L ix e, Manifest r 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
>>>
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 Integer)
Nothing>>>
fromListsM Seq [[[1,2,3]],[[4,5,6],[7,8,9]]] :: IO (Array B Ix3 Integer)
*** Exception: DimTooLongException for (Dim 2): expected (Sz1 1), got (Sz1 2)>>>
fromListsM Seq [[1,2,3,4],[5,6,7]] :: IO (Matrix B Integer)
*** Exception: DimTooShortException for (Dim 1): expected (Sz1 4), got (Sz1 3)
Since: 0.3.0
:: forall r ix e. (HasCallStack, Ragged L ix e, Manifest r e) | |
=> Comp | Computation startegy to use |
-> [ListItem ix e] | Nested list |
-> Array r ix e |
Same as fromListsM
, but will throw an error on irregular shaped lists.
Note: This function is the same as if you would turn on {-# LANGUAGE OverloadedLists #-}
extension. For that reason you can also use fromList
.
\xs -> fromLists' Seq xs == (fromList Seq xs :: Vector P Int)
Examples
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 ] ]
Since: 0.1.0
toList :: (Index ix, Source r e) => Array r ix e -> [e] Source #
Convert any array to a flat list.
Examples
>>>
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
:: (Ragged L ix e, Shape r ix, Source r e) | |
=> Array r ix e | Array to be converted to nested lists |
-> [ListItem ix e] |
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
>>>
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 e, Index ix, 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
>>>
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 :: (Source r e, Index ix, Index (Lower ix), Index (Lower (Lower ix))) => 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 :: (Source r e, Index ix, Index (Lower ix), Index (Lower (Lower ix)), Index (Lower (Lower (Lower ix)))) => 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
module Data.Massiv.Array.Mutable
Core
module Data.Massiv.Core
Representations
module Data.Massiv.Array.Delayed
module Data.Massiv.Array.Manifest
Stencil
module Data.Massiv.Array.Stencil
Numeric Operations
module Data.Massiv.Array.Numeric