Copyright | (c) Alexey Kuleshevich 2020-2022 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <lehins@yandex.ru> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Vector r e = Array r Ix1 e
- type MVector s r e = MArray s r Ix1 e
- slength :: forall r ix e. Stream r ix e => Array r ix e -> Maybe Sz1
- maxLinearSize :: Shape r ix => Array r ix e -> Maybe Sz1
- size :: Size r => Array r ix e -> Sz ix
- 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 :: (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
- head' :: forall r e. (HasCallStack, Source r e) => Vector r e -> e
- shead' :: forall r e. (HasCallStack, Stream r Ix1 e) => Vector r e -> e
- last' :: forall r e. (HasCallStack, Source r e) => Vector r e -> e
- indexM :: (Index ix, Manifest r e, MonadThrow m) => Array r ix e -> ix -> m e
- headM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m e
- sheadM :: forall r e m. (Stream r Ix1 e, MonadThrow m) => Vector r e -> m e
- lastM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m e
- unconsM :: forall r e m. (MonadThrow m, Source r e) => Vector r e -> m (e, Vector r e)
- unsnocM :: forall r e m. (MonadThrow m, Source r e) => Vector r e -> m (Vector r e, e)
- slice :: forall r e. Source r e => Ix1 -> Sz1 -> Vector r e -> Vector r e
- slice' :: forall r e. (HasCallStack, Source r e) => Ix1 -> Sz1 -> Vector r e -> Vector r e
- sliceM :: forall r e m. (Source r e, MonadThrow m) => Ix1 -> Sz1 -> Vector r e -> m (Vector r e)
- sslice :: forall r e. Stream r Ix1 e => Ix1 -> Sz1 -> Vector r e -> Vector DS e
- sliceAt :: forall r e. Source r e => Sz1 -> Vector r e -> (Vector r e, Vector r e)
- sliceAt' :: (HasCallStack, Source r e) => Sz1 -> Vector r e -> (Vector r e, Vector r e)
- sliceAtM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e, Vector r e)
- init :: forall r e. Source r e => Vector r e -> Vector r e
- init' :: forall r e. (HasCallStack, Source r e) => Vector r e -> Vector r e
- initM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m (Vector r e)
- tail :: forall r e. Source r e => Vector r e -> Vector r e
- tail' :: forall r e. (HasCallStack, Source r e) => Vector r e -> Vector r e
- tailM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m (Vector r e)
- take :: Source r e => Sz1 -> Vector r e -> Vector r e
- take' :: forall r e. (HasCallStack, Source r e) => Sz1 -> Vector r e -> Vector r e
- takeM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e)
- takeWhile :: Manifest r e => (e -> Bool) -> Vector r e -> Vector r e
- stake :: forall r e. Stream r Ix1 e => Sz1 -> Vector r e -> Vector DS e
- drop :: forall r e. Source r e => Sz1 -> Vector r e -> Vector r e
- dropWhile :: forall r e. Manifest r e => (e -> Bool) -> Vector r e -> Vector r e
- drop' :: forall r e. (HasCallStack, Source r e) => Sz1 -> Vector r e -> Vector r e
- dropM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e)
- sdrop :: forall r e. Stream r Ix1 e => Sz1 -> Vector r e -> Vector DS e
- empty :: forall r ix e. Load r ix e => Array r ix e
- sempty :: Vector DS e
- singleton :: forall r ix e. Load r ix e => e -> Array r ix e
- ssingleton :: e -> Vector DS e
- cons :: forall r e. (Size r, Load r Ix1 e) => e -> Vector r e -> Vector DL e
- snoc :: forall r e. (Size r, Load r Ix1 e) => Vector r e -> e -> Vector DL e
- replicate :: Load r ix e => Comp -> Sz ix -> e -> Array r ix e
- sreplicate :: Sz1 -> e -> Vector DS e
- generate :: Comp -> Sz1 -> (Ix1 -> e) -> Vector D e
- sgenerate :: Sz1 -> (Ix1 -> e) -> Vector DS e
- siterate :: (e -> e) -> e -> Vector DS e
- siterateN :: Sz1 -> (e -> e) -> e -> Vector DS e
- sreplicateM :: forall e m. Monad m => Sz1 -> m e -> m (Vector DS e)
- sgenerateM :: forall e m. Monad m => Sz1 -> (Ix1 -> m e) -> m (Vector DS e)
- siterateNM :: forall e m. Monad m => Sz1 -> (e -> m e) -> e -> m (Vector DS e)
- sunfoldr :: forall e s. (s -> Maybe (e, s)) -> s -> Vector DS e
- sunfoldrM :: forall e s m. Monad m => (s -> m (Maybe (e, s))) -> s -> m (Vector DS e)
- sunfoldrN :: forall e s. Sz1 -> (s -> Maybe (e, s)) -> s -> Vector DS e
- sunfoldrNM :: forall e s m. Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e)
- sunfoldrExactN :: forall e s. Sz1 -> (s -> (e, s)) -> s -> Vector DS e
- sunfoldrExactNM :: forall e s m. Monad m => Sz1 -> (s -> m (e, s)) -> s -> m (Vector DS e)
- (...) :: Index ix => ix -> ix -> Array D ix ix
- (..:) :: Index ix => ix -> ix -> Array D ix ix
- enumFromN :: Num e => Comp -> e -> Sz1 -> Vector D e
- senumFromN :: Num e => e -> Sz1 -> Vector DS e
- enumFromStepN :: Num e => Comp -> e -> e -> Sz1 -> Vector D e
- senumFromStepN :: Num e => e -> e -> Sz1 -> Vector DS e
- sappend :: forall r1 r2 e. (Stream r1 Ix1 e, Stream r2 Ix1 e) => Vector r1 e -> Vector r2 e -> Vector DS e
- sconcat :: forall r e. Stream r Ix1 e => [Vector r e] -> Vector DS e
- smap :: forall r ix a b. Stream r ix a => (a -> b) -> Array r ix a -> Vector DS b
- simap :: forall r ix a b. Stream r ix a => (ix -> a -> b) -> Array r ix a -> Vector DS b
- straverse :: forall r ix a b f. (Stream r ix a, Applicative f) => (a -> f b) -> Array r ix a -> f (Vector DS b)
- sitraverse :: forall r ix a b f. (Stream r ix a, Applicative f) => (ix -> a -> f b) -> Array r ix a -> f (Vector DS b)
- smapM :: forall r ix a b m. (Stream r ix a, Monad m) => (a -> m b) -> Array r ix a -> m (Vector DS b)
- smapM_ :: forall r ix a b m. (Stream r ix a, Monad m) => (a -> m b) -> Array r ix a -> m ()
- simapM :: forall r ix a b m. (Stream r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m (Vector DS b)
- simapM_ :: forall r ix a b m. (Stream r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m ()
- sforM :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (a -> m b) -> m (Vector DS b)
- sforM_ :: (Stream r ix a, Monad m) => Array r ix a -> (a -> m b) -> m ()
- siforM :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m (Vector DS b)
- siforM_ :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m ()
- szip :: forall ra rb a b. (Stream ra Ix1 a, Stream rb Ix1 b) => Vector ra a -> Vector rb b -> Vector DS (a, b)
- szip3 :: forall ra rb rc a b c. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => Vector ra a -> Vector rb b -> Vector rc c -> Vector DS (a, b, c)
- szip4 :: forall ra rb rc rd a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS (a, b, c, d)
- szip5 :: forall ra rb rc rd re a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS (a, b, c, d, e)
- szip6 :: forall ra rb rc rd re rf a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS (a, b, c, d, e, f)
- szipWith :: forall ra rb a b c. (Stream ra Ix1 a, Stream rb Ix1 b) => (a -> b -> c) -> Vector ra a -> Vector rb b -> Vector DS c
- szipWith3 :: forall ra rb rc a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => (a -> b -> c -> d) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector DS d
- szipWith4 :: forall ra rb rc rd a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => (a -> b -> c -> d -> e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS e
- szipWith5 :: forall ra rb rc rd re a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => (a -> b -> c -> d -> e -> f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS f
- szipWith6 :: forall ra rb rc rd re rf a b c d e f g. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => (a -> b -> c -> d -> e -> f -> g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS g
- sizipWith :: forall ra rb a b c. (Stream ra Ix1 a, Stream rb Ix1 b) => (Ix1 -> a -> b -> c) -> Vector ra a -> Vector rb b -> Vector DS c
- sizipWith3 :: forall ra rb rc a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => (Ix1 -> a -> b -> c -> d) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector DS d
- sizipWith4 :: forall ra rb rc rd a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => (Ix1 -> a -> b -> c -> d -> e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS e
- sizipWith5 :: forall ra rb rc rd re a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => (Ix1 -> a -> b -> c -> d -> e -> f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS f
- sizipWith6 :: forall ra rb rc rd re rf a b c d e f g. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => (Ix1 -> a -> b -> c -> d -> e -> f -> g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS g
- szipWithM :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (a -> b -> m c) -> Vector ra a -> Vector rb b -> m (Vector DS c)
- szipWith3M :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m (Vector DS d)
- szipWith4M :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m (Vector DS e)
- szipWith5M :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m (Vector DS f)
- szipWith6M :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m (Vector DS g)
- sizipWithM :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (Ix1 -> a -> b -> m c) -> Vector ra a -> Vector rb b -> m (Vector DS c)
- sizipWith3M :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (Ix1 -> a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m (Vector DS d)
- sizipWith4M :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (Ix1 -> a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m (Vector DS e)
- sizipWith5M :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m (Vector DS f)
- sizipWith6M :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m (Vector DS g)
- szipWithM_ :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (a -> b -> m c) -> Vector ra a -> Vector rb b -> m ()
- szipWith3M_ :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m ()
- szipWith4M_ :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m ()
- szipWith5M_ :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m ()
- szipWith6M_ :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m ()
- sizipWithM_ :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (Ix1 -> a -> b -> m c) -> Vector ra a -> Vector rb b -> m ()
- sizipWith3M_ :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (Ix1 -> a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m ()
- sizipWith4M_ :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (Ix1 -> a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m ()
- sizipWith5M_ :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m ()
- sizipWith6M_ :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m ()
- sfilter :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Vector DS e
- sifilter :: forall r ix e. Stream r ix e => (ix -> e -> Bool) -> Array r ix e -> Vector DS e
- sfilterM :: forall r ix e f. (Stream r ix e, Applicative f) => (e -> f Bool) -> Array r ix e -> f (Vector DS e)
- sifilterM :: forall r ix e f. (Stream r ix e, Applicative f) => (ix -> e -> f Bool) -> Array r ix e -> f (Vector DS e)
- smapMaybe :: forall r ix a b. Stream r ix a => (a -> Maybe b) -> Array r ix a -> Vector DS b
- smapMaybeM :: forall r ix a b f. (Stream r ix a, Applicative f) => (a -> f (Maybe b)) -> Array r ix a -> f (Vector DS b)
- scatMaybes :: forall r ix a. Stream r ix (Maybe a) => Array r ix (Maybe a) -> Vector DS a
- simapMaybe :: forall r ix a b. Stream r ix a => (ix -> a -> Maybe b) -> Array r ix a -> Vector DS b
- simapMaybeM :: forall r ix a b f. (Stream r ix a, Applicative f) => (ix -> a -> f (Maybe b)) -> Array r ix a -> f (Vector DS b)
- findIndex :: (Index ix, Manifest r e) => (e -> Bool) -> Array r ix e -> Maybe ix
- sfoldl :: forall r ix e a. Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> a
- sfoldlM :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m a
- sfoldlM_ :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m ()
- sifoldl :: forall r ix e a. Stream r ix e => (a -> ix -> e -> a) -> a -> Array r ix e -> a
- sifoldlM :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m a
- sifoldlM_ :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m ()
- sfoldl1' :: forall r ix e. (HasCallStack, Stream r ix e) => (e -> e -> e) -> Array r ix e -> e
- sfoldl1M :: forall r ix e m. (Stream r ix e, MonadThrow m) => (e -> e -> m e) -> Array r ix e -> m e
- sfoldl1M_ :: forall r ix e m. (Stream r ix e, MonadThrow m) => (e -> e -> m e) -> Array r ix e -> m ()
- sor :: forall r ix. Stream r ix Bool => Array r ix Bool -> Bool
- sand :: forall r ix. Stream r ix Bool => Array r ix Bool -> Bool
- sall :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Bool
- sany :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Bool
- ssum :: forall r ix e. (Num e, Stream r ix e) => Array r ix e -> e
- sproduct :: forall r ix e. (Num e, Stream r ix e) => Array r ix e -> e
- smaximum' :: forall r ix e. (HasCallStack, Ord e, Stream r ix e) => Array r ix e -> e
- smaximumM :: forall r ix e m. (Ord e, Stream r ix e, MonadThrow m) => Array r ix e -> m e
- sminimum' :: forall r ix e. (HasCallStack, Ord e, Stream r ix e) => Array r ix e -> e
- sminimumM :: forall r ix e m. (Ord e, Stream r ix e, MonadThrow m) => Array r ix e -> m e
- sprescanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a
- spostscanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a
- spostscanlAcc :: Stream r ix e => (c -> e -> (a, c)) -> c -> Array r ix e -> Vector DS a
- sscanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a
- sscanl1 :: Stream r ix e => (e -> e -> e) -> Array r ix e -> Vector DS e
- stoList :: forall r ix e. Stream r ix e => Array r ix e -> [e]
- fromList :: forall r e. Manifest r e => Comp -> [e] -> Vector r e
- sfromList :: [e] -> Vector DS e
- sfromListN :: Sz1 -> [e] -> Vector DS 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
- 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
- module Data.Massiv.Core
- module Data.Massiv.Array.Delayed
- module Data.Massiv.Array.Manifest
- module Data.Massiv.Array.Mutable
Documentation
type Vector r e = Array r Ix1 e Source #
Type synonym for a single dimension array, or simply a flat vector.
Since: 0.5.0
type MVector s r e = MArray s r Ix1 e Source #
Type synonym for a single dimension mutable array, or simply a flat mutable vector.
Since: 0.5.0
Accessors
Size
slength :: forall r ix e. Stream r ix e => Array r ix e -> Maybe Sz1 Source #
O(1) - Get the length of a Stream
array, but only if it is known exactly in
constant time without looking at any of the elements in the array.
Related: maxLinearSize
, size
, elemsCount
and totalElem
Examples
>>>
slength $ sfromList []
Nothing>>>
slength $ sreplicate 5 ()
Just (Sz1 5)>>>
slength $ makeArrayLinearR D Seq (Sz1 5) id
Just (Sz1 5)>>>
slength $ sunfoldr (\x -> Just (x, x)) (0 :: Int)
Nothing>>>
slength $ sunfoldrN 10 (\x -> Just (x, x)) (0 :: Int)
Nothing>>>
slength $ sunfoldrExactN 10 (\x -> (x, x)) (0 :: Int)
Just (Sz1 10)
Similar:
Data.Foldable.
length
- For some data structures, like a list for
example, it is an O(n) operation, because there is a need to evaluate the full spine
and possibly even the elements in order to get the full length. With
Stream
vectors that is not always the case. Data.Vector.Generic.
length
- In the vector package this function will always break fusion, unless it is the only operation that is applied to the vector.
Since: 0.5.0
maxLinearSize :: Shape r ix => Array r ix e -> Maybe Sz1 Source #
O(1) - Get the possible maximum linear size of an immutabe array. If the lookup
of size in constant time is not possible, Nothing
will be returned. This value
will be used as the initial size of the mutable array into which the loading will
happen.
Since: 1.0.0
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
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' :: (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
head' :: forall r e. (HasCallStack, Source r e) => Vector r e -> e Source #
last' :: forall r e. (HasCallStack, Source r e) => Vector r e -> e Source #
O(1) - Get the last element of a Source
vector. Throws an error on empty.
Examples
>>>
last' (Ix1 10 ... 10000000000000)
10000000000000
Similar:
Since: 0.5.0
Monadic Indexing
headM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m e Source #
O(1) - Get the first element of a Source
vector.
Related: head'
, shead'
, sheadM
, unconsM
.
Throws Exceptions: SizeEmptyException
when array is empty
Examples
>>>
headM (Ix1 10 ..: 10000000000000)
10>>>
headM (Ix1 10 ..: 10000000000000) :: Maybe Int
Just 10>>>
headM (empty :: Array D Ix1 Int) :: Maybe Int
Nothing>>>
either show (const "") $ headM (Ix1 10 ..: 10)
"SizeEmptyException: (Sz1 0) corresponds to an empty array"
Similar:
Data.Maybe.
listToMaybe
- It also a safe way to get the head of the list,
except it is restricted to
Maybe
Since: 0.5.0
sheadM :: forall r e m. (Stream r Ix1 e, MonadThrow m) => Vector r e -> m e Source #
O(1) - Get the first element of a Stream
vector.
Related: head'
, shead'
, headM
, unconsM
.
Throws Exceptions: SizeEmptyException
Examples
>>>
maybe 101 id $ sheadM (empty :: Vector D Int)
101>>>
maybe 101 id $ sheadM (singleton 202 :: Vector D Int)
202>>>
sheadM $ sunfoldr (\x -> Just (x, x)) (0 :: Int)
0>>>
x <- sheadM $ sunfoldr (\_ -> Nothing) (0 :: Int)
*** Exception: SizeEmptyException: (Sz1 0) corresponds to an empty array
Since: 0.5.0
lastM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m e Source #
O(1) - Get the last element of a Source
vector.
Throws Exceptions: SizeEmptyException
Examples
>>>
lastM (Ix1 10 ... 10000000000000)
10000000000000>>>
lastM (Ix1 10 ... 10000000000000) :: Maybe Int
Just 10000000000000>>>
either show (const "") $ lastM (fromList Seq [] :: Array P Ix1 Int)
"SizeEmptyException: (Sz1 0) corresponds to an empty array"
Since: 0.5.0
unconsM :: forall r e m. (MonadThrow m, Source r e) => Vector r e -> m (e, Vector r e) Source #
O(1) - Take one element off of the Source
vector from the left side, as well as
the remaining part of the vector in delayed D
representation.
Related: head'
, shead'
, headM
, sheadM
, cons
Throws Exceptions: SizeEmptyException
Examples
>>>
unconsM (fromList Seq [1,2,3] :: Array P Ix1 Int)
(1,Array P Seq (Sz1 2) [ 2, 3 ])
Similar:
Data.List.
uncons
- Same concept, except it is restricted to
Maybe
instead of the more generalMonadThrow
Since: 0.3.0
unsnocM :: forall r e m. (MonadThrow m, Source r e) => Vector r e -> m (Vector r e, e) Source #
O(1) - Take one element off of the vector from the right side, as well as the remaining part of the vector.
Throws Exceptions: SizeEmptyException
Examples
>>>
unsnocM (fromList Seq [1,2,3] :: Array P Ix1 Int)
(Array P Seq (Sz1 2) [ 1, 2 ],3)
Since: 0.3.0
Slicing
slice :: forall r e. Source r e => Ix1 -> Sz1 -> Vector r e -> Vector r e Source #
O(1) - Take a slice of a Source
vector. Never fails, instead adjusts the indices.
Examples
>>>
slice 10 5 (Ix1 0 ... 10000000000000)
Array D Seq (Sz1 5) [ 10, 11, 12, 13, 14 ]>>>
slice (-10) 5 (Ix1 0 ... 10000000000000)
Array D Seq (Sz1 5) [ 0, 1, 2, 3, 4 ]>>>
slice 9999999999998 50 (Ix1 0 ... 10000000000000)
Array D Seq (Sz1 3) [ 9999999999998, 9999999999999, 10000000000000 ]
Since: 0.5.0
slice' :: forall r e. (HasCallStack, Source r e) => Ix1 -> Sz1 -> Vector r e -> Vector r e Source #
O(1) - Take a slice of a Source
vector. Throws an error on incorrect indices.
Examples
>>>
slice' 10 5 (Ix1 0 ... 100)
Array D Seq (Sz1 5) [ 10, 11, 12, 13, 14 ]>>>
slice' 9999999999998 3 (Ix1 0 ... 10000000000000)
Array D Seq (Sz1 3) [ 9999999999998, 9999999999999, 10000000000000 ]
Since: 0.5.0
:: forall r e m. (Source r e, MonadThrow m) | |
=> Ix1 | Starting index |
-> Sz1 | Number of elements to take from the Source vector |
-> Vector r e | Source vector to take a slice from |
-> m (Vector r e) |
O(1) - Take a slice of a Source
vector. Throws an error on incorrect indices.
Throws Exceptions: SizeSubregionException
Examples
>>>
sliceM 10 5 (Ix1 0 ... 100)
Array D Seq (Sz1 5) [ 10, 11, 12, 13, 14 ]>>>
sliceM (-10) 5 (Ix1 0 ... 100)
*** Exception: SizeSubregionException: (Sz1 101) is to small for -10 (Sz1 5)>>>
sliceM 98 50 (Ix1 0 ... 100)
*** Exception: SizeSubregionException: (Sz1 101) is to small for 98 (Sz1 50)>>>
sliceM 9999999999998 3 (Ix1 0 ... 10000000000000)
Array D Seq (Sz1 3) [ 9999999999998, 9999999999999, 10000000000000 ]
Since: 0.5.0
:: forall r e. Stream r Ix1 e | |
=> Ix1 | Starting index |
-> Sz1 | Number of elements to take from the stream vector |
-> Vector r e | Stream vector to take a slice from |
-> Vector DS e |
Take a slice of a Stream
vector. Never fails, instead adjusts the indices.
Examples
>>>
sslice 10 5 (Ix1 0 ... 10000000000000)
Array DS Seq (Sz1 5) [ 10, 11, 12, 13, 14 ]>>>
sslice 10 5 (sfromList [0 :: Int .. ])
Array DS Seq (Sz1 5) [ 10, 11, 12, 13, 14 ]>>>
sslice (-10) 5 (Ix1 0 ... 10000000000000)
Array DS Seq (Sz1 5) [ 0, 1, 2, 3, 4 ]
Unlike slice
it has to iterate through each element until the staring index is reached,
therefore something like sslice 9999999999998 50 (Ix1 0 ... 10000000000000)
will not
be feasable.
>>>
import System.Timeout (timeout)
>>>
let smallArr = sslice 9999999999998 50 (Ix1 0 ... 10000000000000)
>>>
timeout 500000 (computeIO smallArr :: IO (Array P Ix1 Int))
Nothing
Since: 0.5.0
sliceAtM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e, Vector r e) Source #
Init
init :: forall r e. Source r e => Vector r e -> Vector r e Source #
O(1) - Get a vector without the last element. Never fails.
Examples
>>>
import Data.Massiv.Array as A
>>>
A.init (0 ..: 10)
Array D Seq (Sz1 9) [ 0, 1, 2, 3, 4, 5, 6, 7, 8 ]>>>
A.init (empty :: Array D Ix1 Int)
Array D Seq (Sz1 0) [ ]
Since: 0.5.0
init' :: forall r e. (HasCallStack, Source r e) => Vector r e -> Vector r e Source #
O(1) - Get a vector without the last element. Throws an error on empty
Examples
>>>
init' (0 ..: 10)
Array D Seq (Sz1 9) [ 0, 1, 2, 3, 4, 5, 6, 7, 8 ]
Since: 0.5.0
initM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m (Vector r e) Source #
O(1) - Get a vector without the last element. Throws an error on empty
Examples
>>>
import Data.Massiv.Array as A
>>>
initM (0 ..: 10)
Array D Seq (Sz1 9) [ 0, 1, 2, 3, 4, 5, 6, 7, 8 ]>>>
maybe 0 A.sum $ initM (0 ..: 10)
36>>>
maybe 0 A.sum $ initM (empty :: Array D Ix1 Int)
0
Since: 0.5.0
Tail
tail :: forall r e. Source r e => Vector r e -> Vector r e Source #
O(1) - Get a vector without the first element. Never fails
Examples
>>>
import Data.Massiv.Array as A
>>>
A.tail (0 ..: 10)
Array D Seq (Sz1 9) [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ]>>>
A.tail (empty :: Array D Ix1 Int)
Array D Seq (Sz1 0) [ ]
Since: 0.5.0
tail' :: forall r e. (HasCallStack, Source r e) => Vector r e -> Vector r e Source #
O(1) - Get a vector without the first element. Throws an error on empty
Examples
λ> tail' (0 ..: 10) Array D Seq (Sz1 9) [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ] λ> tail' (empty :: Array D Ix1 Int) Array D *** Exception: SizeEmptyException: (Sz1 0) corresponds to an empty array
Since: 0.5.0
tailM :: forall r e m. (Source r e, MonadThrow m) => Vector r e -> m (Vector r e) Source #
O(1) - Get the vector without the first element. Throws an error on empty
Examples
>>>
import Data.Massiv.Array as A
>>>
tailM (0 ..: 10)
Array D Seq (Sz1 9) [ 1, 2, 3, 4, 5, 6, 7, 8, 9 ]>>>
maybe 0 A.sum $ tailM (0 ..: 10)
45>>>
maybe 0 A.sum $ tailM (empty :: Array D Ix1 Int)
0
Since: 0.5.0
Take
take :: Source r e => Sz1 -> Vector r e -> Vector r e Source #
O(1) - Take first n
elements from a vector. This function never fails and has
similar semantics as the take
for lists.
Examples
>>>
import Data.Massiv.Array as A
>>>
A.take 5 (0 ..: 10)
Array D Seq (Sz1 5) [ 0, 1, 2, 3, 4 ]>>>
A.take 0 (0 ..: 10)
Array D Seq (Sz1 0) [ ]>>>
A.take 100 (0 ..: 10)
Array D Seq (Sz1 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9 ]
Since: 0.5.0
take' :: forall r e. (HasCallStack, Source r e) => Sz1 -> Vector r e -> Vector r e Source #
O(1) - Get the vector with the first n
elements. Throws an error size is less
than n
.
Examples
>>>
take' 0 (0 ..: 0)
Array D Seq (Sz1 0) [ ]>>>
take' 5 (0 ..: 10)
Array D Seq (Sz1 5) [ 0, 1, 2, 3, 4 ]
Since: 0.5.0
takeM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e) Source #
O(1) - Get the vector with the first n
elements. Throws an error size is less than n
Examples
>>>
import Data.Massiv.Array as A
>>>
takeM 5 (0 ..: 10)
Array D Seq (Sz1 5) [ 0, 1, 2, 3, 4 ]>>>
maybe 0 A.sum $ takeM 5 (0 ..: 10)
10>>>
maybe (-1) A.sum $ takeM 15 (0 ..: 10)
-1>>>
takeM 15 (0 ..: 10)
*** Exception: SizeSubregionException: (Sz1 10) is to small for 0 (Sz1 15)
Since: 0.5.0
takeWhile :: Manifest r e => (e -> Bool) -> Vector r e -> Vector r e Source #
Slice a manifest vector in such a way that it will contain all initial elements that satisfy the supplied predicate.
Since: 0.5.5
Drop
drop :: forall r e. Source r e => Sz1 -> Vector r e -> Vector r e Source #
O(1) - Drop n
elements from a vector. This function never fails and has
similar semantics as the drop
for lists.
Examples
>>>
import Data.Massiv.Array as A
>>>
v = makeVectorR D Seq 10 id
>>>
v
Array D Seq (Sz1 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9 ]>>>
A.drop 5 v
Array D Seq (Sz1 5) [ 5, 6, 7, 8, 9 ]>>>
A.drop 25 v
Array D Seq (Sz1 0) [ ]
Since: 0.5.0
dropWhile :: forall r e. Manifest r e => (e -> Bool) -> Vector r e -> Vector r e Source #
Slice a manifest vector in such a way that it will not contain all initial elements that satisfy the supplied predicate.
Since: 0.5.5
drop' :: forall r e. (HasCallStack, Source r e) => Sz1 -> Vector r e -> Vector r e Source #
O(1) - Drop n
elements from a vector. Unlike drop
, this function will
produce an error when supplied number of elements to drop is larger than size
of the supplied vector
Examples
Since: 0.5.0
dropM :: forall r e m. (Source r e, MonadThrow m) => Sz1 -> Vector r e -> m (Vector r e) Source #
Examples
Since: 0.5.0
sdrop :: forall r e. Stream r Ix1 e => Sz1 -> Vector r e -> Vector DS e Source #
Keep all but the first n
elements from the delayed stream vector.
Examples
Since: 0.5.0
Construction
Initialization
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
ssingleton :: e -> Vector DS e Source #
Create a delayed stream vector with a single element
Examples
Since: 0.5.0
cons :: forall r e. (Size r, Load r Ix1 e) => e -> Vector r e -> Vector DL e Source #
O(1) - Add an element to the vector from the left side
Since: 0.3.0
snoc :: forall r e. (Size r, Load r Ix1 e) => Vector r e -> e -> Vector DL e Source #
O(1) - Add an element to the vector from the right side
Since: 0.3.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
sreplicate :: Sz1 -> e -> Vector DS e Source #
Replicate the same element n
times
Examples
Since: 0.5.0
generate :: Comp -> Sz1 -> (Ix1 -> e) -> Vector D e Source #
Create a delayed vector of length n
with a function that maps an index to an
element. Same as makeLinearArray
Examples
Since: 0.5.0
sgenerate :: Sz1 -> (Ix1 -> e) -> Vector DS e Source #
Create a delayed stream vector of length n
with a function that maps an index to an
element. Same as makeLinearArray
Examples
Since: 0.5.0
siterate :: (e -> e) -> e -> Vector DS e Source #
Create a delayed stream vector of infinite length by repeatedly applying a function to the initial value.
Examples
>>>
stake 10 $ siterate succ 'a'
Array DS Seq (Sz1 10) [ 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j' ]
Since: 0.5.2
siterateN :: Sz1 -> (e -> e) -> e -> Vector DS e Source #
Create a delayed stream vector of length n
by repeatedly applying a function to the
initial value.
Examples
>>>
siterateN 10 succ 'a'
Array DS Seq (Sz1 10) [ 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j' ]
Since: 0.5.0
Monadic initialization
sreplicateM :: forall e m. Monad m => Sz1 -> m e -> m (Vector DS e) Source #
Create a vector by using the same monadic action n
times
Examples
Since: 0.5.0
sgenerateM :: forall e m. Monad m => Sz1 -> (Ix1 -> m e) -> m (Vector DS e) Source #
Create a delayed stream vector of length n
with a monadic action that from an index
generates an element.
Examples
Since: 0.5.0
siterateNM :: forall e m. Monad m => Sz1 -> (e -> m e) -> e -> m (Vector DS e) Source #
Create a delayed stream vector of length n
by repeatedly apply a monadic action to
the initial value.
Examples
Since: 0.5.0
Unfolding
sunfoldr :: forall e s. (s -> Maybe (e, s)) -> s -> Vector DS e Source #
Right unfolding function. Useful when it is unknown ahead of time how many elements a vector will have.
Example
>>>
import Data.Massiv.Array as A
>>>
sunfoldr (\i -> if i < 9 then Just (i * i, i + 1) else Nothing) (0 :: Int)
Array DS Seq (Sz1 9) [ 0, 1, 4, 9, 16, 25, 36, 49, 64 ]
Since: 0.5.0
sunfoldrM :: forall e s m. Monad m => (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #
O(n) - Same as sunfoldr
, but with monadic generating function.
Examples
>>>
import Control.Monad (when, guard)
>>>
sunfoldrM (\i -> when (i == 0) (Left "Zero denominator") >> Right (guard (i < 5) >> Just (100 `div` i, i + 1))) (-10 :: Int)
Left "Zero denominator">>>
sunfoldrM (\i -> when (i == 0) (Left "Zero denominator") >> Right (guard (i < -5) >> Just (100 `div` i, i + 1))) (-10 :: Int)
Right (Array DS Seq (Sz1 5) [ -10, -12, -13, -15, -17 ] )
Since: 0.5.0
:: forall e s. Sz1 |
|
-> (s -> Maybe (e, s)) | Unfolding function. Stops when |
-> s | Inititial element. |
-> Vector DS e |
O(n) - Right unfolding function with at most n
number of elements.
Example
>>>
import Data.Massiv.Array as A
>>>
sunfoldrN 9 (\i -> Just (i*i, i + 1)) (0 :: Int)
Array DS Seq (Sz1 9) [ 0, 1, 4, 9, 16, 25, 36, 49, 64 ]
Since: 0.5.0
sunfoldrNM :: forall e s m. Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #
O(n) - Same as sunfoldrN
, but with monadic generating function.
Examples
>>>
import Control.Monad (guard)
>>>
sunfoldrNM 6 (\i -> print i >> pure (guard (i < 5) >> Just (i * i, i + 1))) (10 :: Int)
10 Array DS Seq (Sz1 0) [ ]>>>
sunfoldrNM 6 (\i -> print i >> pure (guard (i < 15) >> Just (i * i, i + 1))) (10 :: Int)
10 11 12 13 14 15 Array DS Seq (Sz1 5) [ 100, 121, 144, 169, 196 ]
Since: 0.5.0
sunfoldrExactN :: forall e s. Sz1 -> (s -> (e, s)) -> s -> Vector DS e Source #
O(n) - Similar to sunfoldrN
, except the length of the resulting vector will be exactly n
Examples
>>>
sunfoldrExactN 10 (\i -> (i * i, i + 1)) (10 :: Int)
Array DS Seq (Sz1 10) [ 100, 121, 144, 169, 196, 225, 256, 289, 324, 361 ]
Since: 0.5.0
sunfoldrExactNM :: forall e s m. Monad m => Sz1 -> (s -> m (e, s)) -> s -> m (Vector DS e) Source #
O(n) - Similar to sunfoldrNM
, except the length of the resulting vector will be exactly n
Examples
λ> sunfoldrExactNM 11 (i -> pure (100 div
i, i + 1)) (-10 :: Int)
Array DS *** Exception: divide by zero
λ> sunfoldrExactNM 11 (i -> guard (i /= 0) >> Just (100 div
i, i + 1)) (-10 :: Int)
Nothing
λ> sunfoldrExactNM 9 (i -> guard (i /= 0) >> Just (100 div
i, i + 1)) (-10 :: Int)
Just (Array DS Seq (Sz1 9)
[ -10, -12, -13, -15, -17, -20, -25, -34, -50 ]
)
Since: 0.5.0
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
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
O(n) - Enumerate from a starting number x
exactly n
times with a step 1
.
Related: senumFromStepN
, enumFromN
, enumFromStepN
, rangeSize
,
rangeStepSize
, range
, rangeStep'
Examples
>>>
senumFromN (10 :: Int) 9
Array DS Seq (Sz1 9) [ 10, 11, 12, 13, 14, 15, 16, 17, 18 ]
Similar:
Prelude.
enumFromTo
- Very similar to
[x .. x + n - 1]
, except thatsenumFromN
is faster and it only works forNum
and not forEnum
elements Data.Vector.Generic.
enumFromN
- Uses exactly the same implementation underneath.
Since: 0.5.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
O(n) - Enumerate from a starting number x
exactly n
times with a custom step value dx
Examples
>>>
senumFromStepN (5 :: Int) 2 10
Array DS Seq (Sz1 10) [ 5, 7, 9, 11, 13, 15, 17, 19, 21, 23 ]
Similar:
Prelude.
enumFrom
- Just like
take n [x, x + dx ..]
, except thatsenumFromN
is faster and it only works forNum
and not forEnum
elements Data.Vector.Generic.
enumFromStepN
- Uses exactly the same implementation underneath.
Since: 0.5.0
Concatenation
sappend :: forall r1 r2 e. (Stream r1 Ix1 e, Stream r2 Ix1 e) => Vector r1 e -> Vector r2 e -> Vector DS e Source #
Append two vectors together
Related: appendM
, appendOuterM
,
Examples
λ> sappend (1 ..: 6) (senumFromStepN 6 (-1) 6) Array DS Seq (Sz1 11) [ 1, 2, 3, 4, 5, 6, 5, 4, 3, 2, 1 ]
Similar:
Data.Semigroup.
<>
DS
andDL
arrays have instances forSemigroup
, so they will work in a similar fashion.sappend
differs in that it acceptsStream
arrays with possibly different representations.Data.List.
++
- Same operation, but for lists.
Data.Vector.Generic.
++
- Uses exactly the same implementation
underneath as
sappend
, except that it cannot append two vectors with different memory representations.
Since: 0.5.0
sconcat :: forall r e. Stream r Ix1 e => [Vector r e] -> Vector DS e Source #
Concat vectors together
Related: concatM
, concatOuterM
,
Examples
>>>
sconcat [2 ... 6, empty, singleton 1, generate Seq 5 id]
Array DS Seq (Sz1 11) [ 2, 3, 4, 5, 6, 1, 0, 1, 2, 3, 4 ]>>>
sconcat [senumFromN 2 5, sempty, ssingleton 1, sgenerate 5 id]
Array DS Seq (Sz1 11) [ 2, 3, 4, 5, 6, 1, 0, 1, 2, 3, 4 ]
Similar:
Data.Monoid.
mconcat
DS
andDL
arrays have instances forMonoid
, so they will work in a similar fashion.sconcat
differs in that it acceptsStream
arrays of other representations.Data.List.
concat
- Same operation, but for lists.
Data.Vector.Generic.
concat
- Uses exactly the same
implementation underneath as
sconcat
.
Since: 0.5.0
smap :: forall r ix a b. Stream r ix a => (a -> b) -> Array r ix a -> Vector DS b Source #
Map a function over a stream vector
Examples
Since: 0.5.0
simap :: forall r ix a b. Stream r ix a => (ix -> a -> b) -> Array r ix a -> Vector DS b Source #
Map an index aware function over a stream vector
Examples
Since: 0.5.0
Monadic mapping
straverse :: forall r ix a b f. (Stream r ix a, Applicative f) => (a -> f b) -> Array r ix a -> f (Vector DS b) Source #
Traverse a stream vector with an applicative function.
Examples
Since: 0.5.0
sitraverse :: forall r ix a b f. (Stream r ix a, Applicative f) => (ix -> a -> f b) -> Array r ix a -> f (Vector DS b) Source #
Traverse a stream vector with an index aware applicative function.
Examples
Since: 0.5.0
smapM :: forall r ix a b m. (Stream r ix a, Monad m) => (a -> m b) -> Array r ix a -> m (Vector DS b) Source #
Traverse a stream vector with a monadic function.
Examples
Since: 0.5.0
smapM_ :: forall r ix a b m. (Stream r ix a, Monad m) => (a -> m b) -> Array r ix a -> m () Source #
Traverse a stream vector with a monadic function, while discarding the result
Examples
Since: 0.5.0
simapM :: forall r ix a b m. (Stream r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m (Vector DS b) Source #
Traverse a stream vector with a monadic index aware function.
Corresponds to: mapM (uncurry f) . imap (,) v
Examples
Since: 0.5.0
simapM_ :: forall r ix a b m. (Stream r ix a, Monad m) => (ix -> a -> m b) -> Array r ix a -> m () Source #
Traverse a stream vector with a monadic index aware function, while discarding the result
Examples
Since: 0.5.0
sforM :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (a -> m b) -> m (Vector DS b) Source #
siforM :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m (Vector DS b) Source #
siforM_ :: forall r ix a b m. (Stream r ix a, Monad m) => Array r ix a -> (ix -> a -> m b) -> m () Source #
Zipping
szip :: forall ra rb a b. (Stream ra Ix1 a, Stream rb Ix1 b) => Vector ra a -> Vector rb b -> Vector DS (a, b) Source #
Zip two vectors together into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Examples
Since: 0.5.0
szip3 :: forall ra rb rc a b c. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => Vector ra a -> Vector rb b -> Vector rc c -> Vector DS (a, b, c) Source #
Zip three vectors together into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szip4 :: forall ra rb rc rd a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS (a, b, c, d) Source #
Zip four vectors together into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szip5 :: forall ra rb rc rd re a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS (a, b, c, d, e) Source #
Zip five vectors together into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szip6 :: forall ra rb rc rd re rf a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS (a, b, c, d, e, f) Source #
Zip six vectors together into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith :: forall ra rb a b c. (Stream ra Ix1 a, Stream rb Ix1 b) => (a -> b -> c) -> Vector ra a -> Vector rb b -> Vector DS c Source #
Zip two vectors together with a binary function into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Examples
Since: 0.5.0
szipWith3 :: forall ra rb rc a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => (a -> b -> c -> d) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector DS d Source #
Zip three vectors together with a ternary function into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith4 :: forall ra rb rc rd a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => (a -> b -> c -> d -> e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS e Source #
Zip four vectors together with a quaternary function into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith5 :: forall ra rb rc rd re a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => (a -> b -> c -> d -> e -> f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS f Source #
Zip five vectors together with a quinary function into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith6 :: forall ra rb rc rd re rf a b c d e f g. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => (a -> b -> c -> d -> e -> f -> g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS g Source #
Zip six vectors together with a senary function into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
sizipWith :: forall ra rb a b c. (Stream ra Ix1 a, Stream rb Ix1 b) => (Ix1 -> a -> b -> c) -> Vector ra a -> Vector rb b -> Vector DS c Source #
Just like szipWith
, zip two vectors together, but with an index aware
function. The length of a resulting vector will be the smallest length of the
supplied vectors.
Examples
Since: 0.5.0
sizipWith3 :: forall ra rb rc a b c d. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c) => (Ix1 -> a -> b -> c -> d) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector DS d Source #
Just like szipWith3
, zip three vectors together, but with an index aware
function. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
sizipWith4 :: forall ra rb rc rd a b c d e. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d) => (Ix1 -> a -> b -> c -> d -> e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector DS e Source #
Just like szipWith4
, zip four vectors together, but with an index aware
function. The length of a resulting vector will be the smallest
length of the supplied vectors.
Since: 0.5.0
sizipWith5 :: forall ra rb rc rd re a b c d e f. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e) => (Ix1 -> a -> b -> c -> d -> e -> f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector DS f Source #
Just like szipWith5
, zip five vectors together, but with an index aware
function. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
sizipWith6 :: forall ra rb rc rd re rf a b c d e f g. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f) => (Ix1 -> a -> b -> c -> d -> e -> f -> g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> Vector DS g Source #
Just like szipWith6
, zip six vectors together, but with an index aware
function. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
Monadic zipping
szipWithM :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (a -> b -> m c) -> Vector ra a -> Vector rb b -> m (Vector DS c) Source #
Zip two vectors together with a binary monadic action into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Examples
Since: 0.5.0
szipWith3M :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m (Vector DS d) Source #
Zip three vectors together with a ternary monadic action into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith4M :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m (Vector DS e) Source #
Zip four vectors together with a quaternary monadic action into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith5M :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m (Vector DS f) Source #
Zip five vectors together with a quinary monadic action into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
szipWith6M :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m (Vector DS g) Source #
Zip six vectors together with a senary monadic action into a vector. The length of a resulting vector will be the smallest length of the supplied vectors.
Since: 0.5.0
sizipWithM :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (Ix1 -> a -> b -> m c) -> Vector ra a -> Vector rb b -> m (Vector DS c) Source #
Just like szipWithM
, zip two vectors together, but with an index aware
monadic action. The length of a resulting vector will be the smallest length of the
supplied vectors.
Examples
Since: 0.5.0
sizipWith3M :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (Ix1 -> a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m (Vector DS d) Source #
Just like szipWith3M
, zip three vectors together, but with an index aware
monadic action. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
sizipWith4M :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (Ix1 -> a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m (Vector DS e) Source #
Just like szipWith4M
, zip four vectors together, but with an index aware
monadic action. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
sizipWith5M :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m (Vector DS f) Source #
Just like szipWith6M
, zip five vectors together, but with an index aware
monadic action. The length of a resulting vector will be the smallest length of the
supplied vectors.
Since: 0.5.0
sizipWith6M :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m (Vector DS g) Source #
Just like szipWith6M
, zip six vectors together, but with an index aware
monadic action. The length of a resulting vector will be the smallest length of the
supplied vectors.
Examples
Since: 0.5.0
szipWithM_ :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (a -> b -> m c) -> Vector ra a -> Vector rb b -> m () Source #
Similar to szipWithM
, zip two vectors together with a binary monadic
action, while discarding its result. The action will be invoked as many times as
the length of the smallest vector.
Examples
Since: 0.5.0
szipWith3M_ :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m () Source #
Similar to szipWith3M
, zip three vectors together with a ternary monadic
action, while discarding its result. The action will be invoked as many times as
the length of the smallest vector.
Since: 0.5.0
szipWith4M_ :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m () Source #
Similar to szipWith4M
, zip four vectors together with a quaternary monadic
action, while discarding its result. The action will be invoked as many times as
the length of the smallest vector.
Since: 0.5.0
szipWith5M_ :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m () Source #
Similar to szipWith5M
, zip five vectors together with a quinary monadic
action, while discarding its result. The action will be invoked as many times as
the length of the smallest vector.
Since: 0.5.0
szipWith6M_ :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m () Source #
Similar to szipWith6M
, zip six vectors together with a senary monadic
action, while discarding its result. The action will be invoked as many times as
the length of the smallest vector.
Since: 0.5.0
sizipWithM_ :: forall ra rb a b c m. (Stream ra Ix1 a, Stream rb Ix1 b, Monad m) => (Ix1 -> a -> b -> m c) -> Vector ra a -> Vector rb b -> m () Source #
Same as szipWithM_
, zip two vectors together, but with an index aware
monadic action. The action will be invoked as many times as the length of the
smallest vector.
Examples
Since: 0.5.0
sizipWith3M_ :: forall ra rb rc a b c d m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Monad m) => (Ix1 -> a -> b -> c -> m d) -> Vector ra a -> Vector rb b -> Vector rc c -> m () Source #
Same as szipWith3M_
, zip three vectors together, but with an index aware
monadic action. The action will be invoked as many times as the length of the
smallest vector.
Since: 0.5.0
sizipWith4M_ :: forall ra rb rc rd a b c d e m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Monad m) => (Ix1 -> a -> b -> c -> d -> m e) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> m () Source #
Same as szipWith4M_
, zip four vectors together, but with an index aware
monadic action. The action will be invoked as many times as the length of the
smallest vector.
Since: 0.5.0
sizipWith5M_ :: forall ra rb rc rd re a b c d e f m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> m f) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> m () Source #
Same as szipWith5M_
, zip five vectors together, but with an index aware
monadic action. The action will be invoked as many times as the length of the
smallest vector.
Since: 0.5.0
sizipWith6M_ :: forall ra rb rc rd re rf a b c d e f g m. (Stream ra Ix1 a, Stream rb Ix1 b, Stream rc Ix1 c, Stream rd Ix1 d, Stream re Ix1 e, Stream rf Ix1 f, Monad m) => (Ix1 -> a -> b -> c -> d -> e -> f -> m g) -> Vector ra a -> Vector rb b -> Vector rc c -> Vector rd d -> Vector re e -> Vector rf f -> m () Source #
Same as szipWith6M_
, zip six vectors together, but with an index aware
monadic action. The action will be invoked as many times as the length of the
smallest vector.
Since: 0.5.0
Predicates
Filtering
sfilter :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Vector DS e Source #
Sequentially filter out elements from the array according to the supplied predicate.
Example
>>>
import Data.Massiv.Array as A
>>>
arr = makeArrayR D Seq (Sz2 3 4) fromIx2
>>>
arr
Array D Seq (Sz (3 :. 4)) [ [ (0,0), (0,1), (0,2), (0,3) ] , [ (1,0), (1,1), (1,2), (1,3) ] , [ (2,0), (2,1), (2,2), (2,3) ] ]>>>
sfilter (even . fst) arr
Array DS Seq (Sz1 8) [ (0,0), (0,1), (0,2), (0,3), (2,0), (2,1), (2,2), (2,3) ]
Since: 0.5.0
sifilter :: forall r ix e. Stream r ix e => (ix -> e -> Bool) -> Array r ix e -> Vector DS e Source #
sfilterM :: forall r ix e f. (Stream r ix e, Applicative f) => (e -> f Bool) -> Array r ix e -> f (Vector DS e) Source #
Sequentially filter out elements from the array according to the supplied applicative predicate.
Example
>>>
import Data.Massiv.Array as A
>>>
arr = makeArrayR D Seq (Sz2 3 4) fromIx2
>>>
arr
Array D Seq (Sz (3 :. 4)) [ [ (0,0), (0,1), (0,2), (0,3) ] , [ (1,0), (1,1), (1,2), (1,3) ] , [ (2,0), (2,1), (2,2), (2,3) ] ]>>>
sfilterM (Just . odd . fst) arr
Just (Array DS Seq (Sz1 4) [ (1,0), (1,1), (1,2), (1,3) ] )>>>
sfilterM (\ix@(_, j) -> print ix >> return (even j)) arr
(0,0) (0,1) (0,2) (0,3) (1,0) (1,1) (1,2) (1,3) (2,0) (2,1) (2,2) (2,3) Array DS Seq (Sz1 6) [ (0,0), (0,2), (1,0), (1,2), (2,0), (2,2) ]
Since: 0.5.0
sifilterM :: forall r ix e f. (Stream r ix e, Applicative f) => (ix -> e -> f Bool) -> Array r ix e -> f (Vector DS e) Source #
Similar to filterM
, but filter with an index aware function.
Corresponds to: filterM
(uncurry f) . simap
(,)
Since: 0.5.0
smapMaybe :: forall r ix a b. Stream r ix a => (a -> Maybe b) -> Array r ix a -> Vector DS b Source #
smapMaybeM :: forall r ix a b f. (Stream r ix a, Applicative f) => (a -> f (Maybe b)) -> Array r ix a -> f (Vector DS b) Source #
Similar to smapMaybe
, but with the Applicative
function.
Similar to mapMaybe id $ mapM f arr
Examples
Since: 0.5.0
simapMaybe :: forall r ix a b. Stream r ix a => (ix -> a -> Maybe b) -> Array r ix a -> Vector DS b Source #
simapMaybeM :: forall r ix a b f. (Stream r ix a, Applicative f) => (ix -> a -> f (Maybe b)) -> Array r ix a -> f (Vector DS b) Source #
findIndex :: (Index ix, Manifest r e) => (e -> Bool) -> Array r ix e -> Maybe ix Source #
O(n) - Perform a row-major search starting at 0
for an element. Returns the index
of the first occurance of an element or Nothing
if a predicate could not be satisifed
after it was applyied to all elements of the array.
Since: 0.5.5
Folding
sfoldl :: forall r ix e a. Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> a Source #
Streaming fold over an array in a row-major fashion with a left biased function and a strict accumulator.
Examples
Since: 0.5.0
sfoldlM :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m a Source #
Examples
Since: 0.5.0
sfoldlM_ :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> e -> m a) -> a -> Array r ix e -> m () Source #
Examples
Since: 0.5.0
sifoldl :: forall r ix e a. Stream r ix e => (a -> ix -> e -> a) -> a -> Array r ix e -> a Source #
Examples
Since: 0.5.0
sifoldlM :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m a Source #
Examples
Since: 0.5.0
sifoldlM_ :: forall r ix e a m. (Stream r ix e, Monad m) => (a -> ix -> e -> m a) -> a -> Array r ix e -> m () Source #
Examples
Since: 0.5.0
sfoldl1' :: forall r ix e. (HasCallStack, Stream r ix e) => (e -> e -> e) -> Array r ix e -> e Source #
Examples
Since: 0.5.0
sfoldl1M :: forall r ix e m. (Stream r ix e, MonadThrow m) => (e -> e -> m e) -> Array r ix e -> m e Source #
Examples
Since: 0.5.0
sfoldl1M_ :: forall r ix e m. (Stream r ix e, MonadThrow m) => (e -> e -> m e) -> Array r ix e -> m () Source #
Examples
Since: 0.5.0
Specialized folds
sall :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Bool Source #
Examples
Since: 0.5.0
sany :: forall r ix e. Stream r ix e => (e -> Bool) -> Array r ix e -> Bool Source #
Examples
Since: 0.5.0
ssum :: forall r ix e. (Num e, Stream r ix e) => Array r ix e -> e Source #
Add all elements of the array together
Related: sum
.
Examples
>>>
import Data.Massiv.Vector as V
>>>
V.ssum $ V.sfromList [10, 3, 70, 5 :: Int]
88
Since: 0.5.0
sproduct :: forall r ix e. (Num e, Stream r ix e) => Array r ix e -> e Source #
Multiply all elements of the array together
Related: product
.
Examples
>>>
import Data.Massiv.Vector as V
>>>
V.sproduct $ V.sfromList [10, 3, 70, 5 :: Int]
10500
Since: 0.5.0
smaximumM :: forall r ix e m. (Ord e, Stream r ix e, MonadThrow m) => Array r ix e -> m e Source #
O(n) - Find the largest value in the array.
Related: smaximum
, maximum
, maximumM
.
Throws Exceptions: SizeEmptyException
when array is empty
Examples
>>>
import Data.Massiv.Vector as V
>>>
V.smaximumM $ V.sfromList [10, 3, 70, 5 :: Int]
70>>>
V.smaximumM (V.empty :: Vector D Int) :: Maybe Int
Nothing
Since: 0.5.0
sminimumM :: forall r ix e m. (Ord e, Stream r ix e, MonadThrow m) => Array r ix e -> m e Source #
O(n) - Find the smallest value in the array.
Related: sminimum'
, minimum
, minimumM
.
Throws Exceptions: SizeEmptyException
when array is empty
Examples
>>>
import Data.Massiv.Vector as V
>>>
V.sminimumM $ V.sfromList [10, 3, 70, 5 :: Int]
3>>>
V.sminimumM (V.empty :: Array D Ix2 Int) :: Maybe Int
Nothing
Since: 0.5.0
Scanning
sprescanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a Source #
O(n) - left scan with strict accumulator. First element is the value of the accumulator. Last element is not included.
Examples
>>>
import Data.Massiv.Vector
>>>
sprescanl min 6 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 6, 6, 5, 5 ]>>>
sprescanl (+) 0 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 0, 10, 15, 85 ]
Since: 1.0.3
spostscanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a Source #
O(n) - left scan with strict accumulator. First element is the result of applying the supplied function.
Examples
>>>
import Data.Massiv.Vector
>>>
spostscanl min 6 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 6, 5, 5, 3 ]>>>
spostscanl (+) 0 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 10, 15, 85, 88 ]
Since: 1.0.3
spostscanlAcc :: Stream r ix e => (c -> e -> (a, c)) -> c -> Array r ix e -> Vector DS a Source #
O(n) - Just like spostscanl
except it is possible to produce a vector with an
element type that differes from accumulator type.
Examples
>>>
import Data.Massiv.Vector
>>>
spostscanlAcc (\x y -> if x < y then (True, x) else (False, y)) 6 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ True, False, True, False ]
Since: 1.0.3
sscanl :: Stream r ix e => (a -> e -> a) -> a -> Array r ix e -> Vector DS a Source #
O(n) - left scan with strict accumulator. First element is the value of the accumulator.
Examples
>>>
import Data.Massiv.Vector
>>>
sscanl min 6 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 5) [ 6, 6, 5, 5, 3 ]>>>
sscanl (+) 0 $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 5) [ 0, 10, 15, 85, 88 ]
Since: 1.0.3
sscanl1 :: Stream r ix e => (e -> e -> e) -> Array r ix e -> Vector DS e Source #
O(n) - left scan with strict accumulator and no initial value for the accumulator.
Examples
>>>
import Data.Massiv.Vector
>>>
sscanl1 min $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 10, 5, 5, 3 ]>>>
sscanl1 (+) $ sfromList [10, 5, 70, 3 :: Int]
Array DS Seq (Sz1 4) [ 10, 15, 85, 88 ]>>>
sscanl1 (+) $ sfromList ([] :: [Int])
Array DS Seq (Sz1 0) [ ]
Since: 1.0.3
Conversions
Lists
stoList :: forall r ix e. Stream r ix e => Array r ix e -> [e] Source #
Convert an array to a list by the means of a delayed stream vector.
Related: toList
Examples
Since: 0.5.0
Convert a flat list into a vector
Since: 0.1.0
sfromList :: [e] -> Vector DS e Source #
Convert a list to a delayed stream vector
Related: fromList
, fromListN
, sfromListN
Examples
>>>
sfromList ([] :: [Int])
Array DS Seq (Sz1 0) [ ]>>>
sfromList ([1,2,3] :: [Int])
Array DS Seq (Sz1 3) [ 1, 2, 3 ]
Since: 0.5.0
sfromListN :: Sz1 -> [e] -> Vector DS e Source #
Convert a list to a delayed stream vector. Length of the resulting vector will be at
most n
. This version isn't really more efficient then sfromList
, but there is
unsafeFromListN
Related: fromList
, fromListN
, sfromList
Examples
>>>
sfromListN 10 [1 :: Int ..]
Array DS Seq (Sz1 10) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 ]>>>
sfromListN 10 [1 :: Int .. 5]
Array DS Seq (Sz1 5) [ 1, 2, 3, 4, 5 ]
Since: 0.5.1
Computation
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
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
Re-exports
module Data.Massiv.Core
module Data.Massiv.Array.Delayed
module Data.Massiv.Array.Manifest
module Data.Massiv.Array.Mutable