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 |
Synopsis
- unsafeMakeLoadArray :: forall ix e. Index ix => Comp -> Sz ix -> Maybe e -> (forall s. Scheduler s () -> Ix1 -> (Ix1 -> e -> ST s ()) -> ST s ()) -> Array DL ix e
- unsafeMakeLoadArrayAdjusted :: forall ix e. Index ix => Comp -> Sz ix -> Maybe e -> (forall s. Scheduler s () -> (Ix1 -> e -> ST s ()) -> ST s ()) -> Array DL ix e
- newtype Sz ix = SafeSz ix
- newtype Stride ix = SafeStride ix
- unsafeIndex :: Source r e => Index ix => Array r ix e -> ix -> e
- unsafePrefIndex :: Source r e => Index ix => Array r ix e -> PrefIndex ix e
- unsafeLinearIndex :: Source r e => Index ix => Array r ix e -> Int -> e
- unsafeLinearIndexM :: (Manifest r e, Index ix) => Array r ix e -> Int -> e
- unsafeBackpermute :: (Index ix', Source r' e, Index ix) => Sz ix -> (ix -> ix') -> Array r' ix' e -> Array D ix e
- unsafeResize :: (Size r, Index ix, Index ix') => Sz ix' -> Array r ix e -> Array r ix' e
- unsafeExtract :: (Source r e, Index ix) => ix -> Sz ix -> Array r ix e -> Array D ix e
- unsafeTransform :: (Index ix', Source r' e', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e
- unsafeTransform2 :: (Index ix1, Source r1 e1, Index ix2, Source r2 e2, Index ix) => (Sz ix1 -> Sz ix2 -> (Sz ix, a)) -> (a -> (ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e
- unsafeSlice :: (Source r e, Index ix, Index (Lower ix), MonadThrow m) => Array r ix e -> ix -> Sz ix -> Dim -> m (Array D (Lower ix) e)
- unsafeOuterSlice :: Source r e => (Index ix, Index (Lower ix)) => Array r ix e -> Sz (Lower ix) -> Int -> Array r (Lower ix) e
- unsafeInnerSlice :: (Source r e, Index ix) => Array r ix e -> Sz (Lower ix) -> Int -> Array D (Lower ix) e
- unsafeLinearSlice :: (Source r e, Index ix) => Ix1 -> Sz1 -> Array r ix e -> Array r Ix1 e
- unsafeResizeMArray :: (Manifest r e, Index ix', Index ix) => Sz ix' -> MArray s r ix e -> MArray s r ix' e
- unsafeLinearSliceMArray :: (Manifest r e, Index ix) => Ix1 -> Sz1 -> MArray s r ix e -> MVector s r e
- unsafeThaw :: (Manifest r e, Index ix, PrimMonad m) => Array r ix e -> m (MArray (PrimState m) r ix e)
- unsafeFreeze :: (Manifest r e, Index ix, PrimMonad m) => Comp -> MArray (PrimState m) r ix e -> m (Array r ix e)
- unsafeNew :: (Manifest r e, Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeLoadIntoST :: (Load r ix e, Manifest r' e) => MVector s r' e -> Array r ix e -> ST s (MArray s r' ix e)
- unsafeLoadIntoIO :: (Load r ix e, Manifest r' e) => MVector RealWorld r' e -> Array r ix e -> IO (MArray RealWorld r' ix e)
- unsafeLoadIntoS :: forall r r' ix e m s. (Load r ix e, Manifest r' e, MonadPrim s m) => MVector s r' e -> Array r ix e -> m (MArray s r' ix e)
- unsafeLoadIntoM :: forall r r' ix e m. (Load r ix e, Manifest r' e, MonadIO m) => MVector RealWorld r' e -> Array r ix e -> m (MArray RealWorld r' ix e)
- unsafeCreateArray :: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) => Comp -> Sz ix -> (Scheduler RealWorld a -> MArray RealWorld r ix e -> m b) -> m ([a], Array r ix e)
- unsafeCreateArray_ :: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) => Comp -> Sz ix -> (Scheduler RealWorld a -> MArray RealWorld r ix e -> m b) -> m (Array r ix e)
- unsafeCreateArrayS :: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) => Sz ix -> (MArray (PrimState m) r ix e -> m a) -> m (a, Array r ix e)
- unsafeRead :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e
- unsafeLinearRead :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> m e
- unsafeWrite :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m ()
- unsafeLinearWrite :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> e -> m ()
- unsafeModify :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> ix -> m e
- unsafeLinearModify :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> Int -> m e
- unsafeSwap :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m (e, e)
- unsafeLinearSwap :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> Int -> m (e, e)
- unsafeLinearSet :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> e -> m ()
- unsafeLinearCopy :: Manifest r e => (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) r ix' e -> Ix1 -> MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> m ()
- unsafeArrayLinearCopy :: Manifest r e => (Index ix', Index ix, PrimMonad m) => Array r ix' e -> Ix1 -> MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> m ()
- unsafeLinearShrink :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeLinearGrow :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e)
- unsafeMallocMArray :: forall ix e m. (Index ix, Storable e, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e)
- unsafeWithPtr :: MonadUnliftIO m => Array S ix e -> (Ptr e -> m b) -> m b
- unsafeArrayToForeignPtr :: Index ix => Array S ix e -> (ForeignPtr e, Int)
- unsafeMArrayToForeignPtr :: Index ix => MArray s S ix e -> (ForeignPtr e, Int)
- unsafeArrayFromForeignPtr :: Storable e => Comp -> ForeignPtr e -> Int -> Sz1 -> Array S Ix1 e
- unsafeArrayFromForeignPtr0 :: Comp -> ForeignPtr e -> Sz1 -> Vector S e
- unsafeMArrayFromForeignPtr :: Storable e => ForeignPtr e -> Int -> Sz1 -> MArray s S Ix1 e
- unsafeMArrayFromForeignPtr0 :: ForeignPtr e -> Sz1 -> MArray s S Ix1 e
- unsafeAtomicReadIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> m Int
- unsafeAtomicWriteIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m ()
- unsafeAtomicModifyIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> (Int -> Int) -> m Int
- unsafeAtomicAddIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicSubIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicAndIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicNandIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicOrIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeAtomicXorIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int
- unsafeCasIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> Int -> m Int
- coerceBoxedArray :: Array BL ix e -> Array B ix e
- coerceNormalBoxedArray :: Array BL ix e -> Array N ix e
- unsafeUnstablePartitionRegionM :: forall r e m. (Manifest r e, PrimMonad m) => MVector (PrimState m) r e -> (e -> m Bool) -> Ix1 -> Ix1 -> m Ix1
- unsafeHead :: Source r e => Vector r e -> e
- unsafeLast :: Source r e => Vector r e -> e
- unsafeIndexM :: (Source r e, Monad m) => Vector r e -> Ix1 -> m e
- unsafeHeadM :: (Monad m, Source r e) => Vector r e -> m e
- unsafeLastM :: (Monad m, Source r e) => Vector r e -> m e
- unsafeInit :: Source r e => Vector r e -> Vector r e
- unsafeTail :: Source r e => Vector r e -> Vector r e
- unsafeTake :: Source r e => Sz1 -> Vector r e -> Vector r e
- unsafeDrop :: Source r e => Sz1 -> Vector r e -> Vector r e
- unsafeUnfoldrN :: Sz1 -> (s -> Maybe (e, s)) -> s -> Vector DS e
- unsafeUnfoldrNM :: Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e)
- unsafeFromListN :: Sz1 -> [e] -> Vector DS e
- makeUnsafeStencil :: Index ix => Sz ix -> ix -> (ix -> (ix -> e) -> a) -> Stencil ix e a
- makeUnsafeConvolutionStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e
- makeUnsafeCorrelationStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e
- unsafeTransformStencil :: (Sz ix' -> Sz ix) -> (ix' -> ix) -> (((ix' -> e) -> (ix' -> e) -> ix' -> a) -> (ix -> e) -> (ix -> e) -> ix -> a) -> Stencil ix' e a -> Stencil ix e a
- data family Array r ix e :: Type
- data family MArray s r ix e :: Type
Creation
:: forall ix e. Index ix | |
=> Comp | Computation strategy to use. Directly affects the scheduler that gets created for the loading function. |
-> Sz ix | Size of the array |
-> Maybe e | An element to use for initialization of the mutable array that will be created in the future |
-> (forall s. Scheduler s () -> Ix1 -> (Ix1 -> e -> ST s ()) -> ST s ()) | This function accepts:
|
-> Array DL ix e |
Specify how an array can be loaded/computed through creation of a DL
array. Unlike
makeLoadArrayS
or makeLoadArray
this function is unsafe, since there is no
guarantee that all elements will be initialized and the supplied element writing
function does not perform any bounds checking.
Since: 0.3.1
unsafeMakeLoadArrayAdjusted :: forall ix e. Index ix => Comp -> Sz ix -> Maybe e -> (forall s. Scheduler s () -> (Ix1 -> e -> ST s ()) -> ST s ()) -> Array DL ix e Source #
Same as unsafeMakeLoadArray
, except will ensure that starting index is correctly
adjusted. Which means the writing function gets one less argument.
Since: 0.5.2
Indexing
Sz
is the size of the array. It describes total number of elements along
each dimension in the array. It is a wrapper around an index of the same
dimension, however it provides type safety preventing mixup with
index. Moreover the Sz
constructor and others such as
Sz1
, Sz2
, ... that
are specialized to specific dimensions, prevent creation of invalid sizes with
negative values by clamping them to zero.
Examples
>>>
import Data.Massiv.Array
>>>
Sz (1 :> 2 :. 3)
Sz (1 :> 2 :. 3)
Sz
has a Num
instance, which is very convenient:
>>>
Sz (1 :> 2 :. 3) + 5
Sz (6 :> 7 :. 8)
However subtraction can sometimes lead to surprising behavior, because size is not allowed to take negative values it will be clamped at 0.
>>>
Sz (1 :> 2 :. 3) - 2
Sz (0 :> 0 :. 1)
Warning: It is always wrong to negate
a size, thus it will result in an
error. For that reason also watch out for partially applied (
, which is
deugared into -
sz)
. See more info about it in
#114.negate
sz
Since: 0.3.0
SafeSz ix | Safe size constructor. It is unsafe to use it without making sure that it does not contain
negative components. Use Since: 0.3.0 |
Instances
(Num ix, Index ix) => Num (Sz ix) Source # | Calling |
Index ix => Show (Sz ix) Source # | |
NFData ix => NFData (Sz ix) Source # | |
Defined in Data.Massiv.Core.Index.Internal | |
Eq ix => Eq (Sz ix) Source # | |
Ord ix => Ord (Sz ix) Source # | |
(UniformRange ix, Index ix) => Random (Sz ix) Source # | |
(UniformRange ix, Index ix) => Uniform (Sz ix) Source # | |
Defined in Data.Massiv.Core.Index.Internal uniformM :: StatefulGen g m => g -> m (Sz ix) # | |
UniformRange ix => UniformRange (Sz ix) Source # | |
Defined in Data.Massiv.Core.Index.Internal |
Stride provides a way to ignore elements of an array if an index is divisible by a
corresponding value in a stride. So, for a Stride (i :. j)
only elements with indices will be
kept around:
( 0 :. 0) ( 0 :. j) ( 0 :. 2j) ( 0 :. 3j) ... ( i :. 0) ( i :. j) ( i :. 2j) ( i :. 3j) ... (2i :. 0) (2i :. j) (2i :. 2j) (2i :. 3j) ... ...
Only positive strides make sense, so Stride
pattern synonym constructor will prevent a user
from creating a stride with negative or zero values, thus promoting safety of the library.
Examples:
- Default and minimal stride of
will have no affect and all elements will kept.Stride
(pureIndex
1) - If stride is
, then every 2nd element (i.e. with index 1, 3, 5, ..) will be skipped and only elemnts with indices divisible by 2 will be kept around.Stride
2 - In case of two dimensions, if what you want is to keep all rows divisible by 5, but keep every
column intact then you'd use
Stride (5 :. 1)
.
Since: 0.2.1
SafeStride ix |
Instances
Index ix => Show (Stride ix) Source # | |
NFData ix => NFData (Stride ix) Source # | |
Defined in Data.Massiv.Core.Index.Stride | |
Eq ix => Eq (Stride ix) Source # | |
Ord ix => Ord (Stride ix) Source # | |
Defined in Data.Massiv.Core.Index.Stride | |
(UniformRange ix, Index ix) => Random (Stride ix) Source # | |
(UniformRange ix, Index ix) => Uniform (Stride ix) Source # | |
Defined in Data.Massiv.Core.Index.Stride uniformM :: StatefulGen g m => g -> m (Stride ix) # | |
UniformRange ix => UniformRange (Stride ix) Source # | |
Defined in Data.Massiv.Core.Index.Stride |
unsafeIndex :: Source r e => Index ix => Array r ix e -> ix -> e Source #
Lookup element in the array. No bounds check is performed and access of arbitrary memory is possible when invalid index is supplied.
Since: 0.1.0
unsafePrefIndex :: Source r e => Index ix => Array r ix e -> PrefIndex ix e Source #
Alternative indexing function that can choose an index that is most efficient for underlying representation
Since: 1.0.2
unsafeLinearIndex :: Source r e => Index ix => Array r ix e -> Int -> e Source #
Lookup element in the array using flat index in a row-major fashion. No bounds check is performed
Since: 0.1.0
Manipulations
unsafeBackpermute :: (Index ix', Source r' e, Index ix) => Sz ix -> (ix -> ix') -> Array r' ix' e -> Array D ix e Source #
unsafeResize :: (Size r, Index ix, Index ix') => Sz ix' -> Array r ix e -> Array r ix' e Source #
O(1) - Change the size of an array. Total number of elements should be the same, but it is not validated.
Since: 0.1.0
unsafeExtract :: (Source r e, Index ix) => ix -> Sz ix -> Array r ix e -> Array D ix e Source #
O(1) - Extract a portion of an array. Staring index and new size are not validated.
unsafeTransform :: (Index ix', Source r' e', Index ix) => (Sz ix' -> (Sz ix, a)) -> (a -> (ix' -> e') -> ix -> e) -> Array r' ix' e' -> Array D ix e Source #
Same transform'
, except no bounds checking is performed, thus making it faster,
but unsafe.
Since: 0.3.0
unsafeTransform2 :: (Index ix1, Source r1 e1, Index ix2, Source r2 e2, Index ix) => (Sz ix1 -> Sz ix2 -> (Sz ix, a)) -> (a -> (ix1 -> e1) -> (ix2 -> e2) -> ix -> e) -> Array r1 ix1 e1 -> Array r2 ix2 e2 -> Array D ix e Source #
Same transform2'
, except no bounds checking is performed, thus making it faster,
but unsafe.
Since: 0.3.0
Slicing
unsafeSlice :: (Source r e, Index ix, Index (Lower ix), MonadThrow m) => Array r ix e -> ix -> Sz ix -> Dim -> m (Array D (Lower ix) e) Source #
O(1) - Take a slice out of an array from within
unsafeOuterSlice :: Source r e => (Index ix, Index (Lower ix)) => Array r ix e -> Sz (Lower ix) -> Int -> Array r (Lower ix) e Source #
O(1) - Take a slice out of an array from the outside
Since: 0.1.0
unsafeInnerSlice :: (Source r e, Index ix) => Array r ix e -> Sz (Lower ix) -> Int -> Array D (Lower ix) e Source #
O(1) - Take a slice out of an array from the inside
unsafeLinearSlice :: (Source r e, Index ix) => Ix1 -> Sz1 -> Array r ix e -> Array r Ix1 e Source #
O(1) - Source arrays also give us ability to look at their linear slices in constant time
Since: 0.5.0
Mutable interface
unsafeResizeMArray :: (Manifest r e, Index ix', Index ix) => Sz ix' -> MArray s r ix e -> MArray s r ix' e Source #
O(1) - Change the size of a mutable array. The actual number of elements should stay the same.
Since: 1.0.0
unsafeLinearSliceMArray :: (Manifest r e, Index ix) => Ix1 -> Sz1 -> MArray s r ix e -> MVector s r e Source #
O(1) - Take a linear slice out of a mutable array.
Since: 1.0.0
unsafeThaw :: (Manifest r e, Index ix, PrimMonad m) => Array r ix e -> m (MArray (PrimState m) r ix e) Source #
Convert immutable array into a mutable array without copy.
Since: 0.1.0
unsafeFreeze :: (Manifest r e, Index ix, PrimMonad m) => Comp -> MArray (PrimState m) r ix e -> m (Array r ix e) Source #
Convert mutable array into an immutable array without copy.
Since: 0.1.0
unsafeNew :: (Manifest r e, Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) r ix e) Source #
Create new mutable array, leaving it's elements uninitialized. Size isn't validated either.
Since: 0.1.0
unsafeLoadIntoST :: (Load r ix e, Manifest r' e) => MVector s r' e -> Array r ix e -> ST s (MArray s r' ix e) Source #
Load into a supplied mutable array sequentially. Returned array does not have to be the same.
Since: 1.0.0
unsafeLoadIntoIO :: (Load r ix e, Manifest r' e) => MVector RealWorld r' e -> Array r ix e -> IO (MArray RealWorld r' ix e) Source #
Same as unsafeLoadIntoST
, but respecting computation strategy.
Since: 1.0.0
unsafeLoadIntoS :: forall r r' ix e m s. (Load r ix e, Manifest r' e, MonadPrim s m) => MVector s r' e -> Array r ix e -> m (MArray s r' ix e) Source #
Load into a supplied mutable vector sequentially. Returned array is not necesserally the same vector as the one that was supplied. It will be the same only if it had enough space to load all the elements in.
Since: 0.5.7
unsafeLoadIntoM :: forall r r' ix e m. (Load r ix e, Manifest r' e, MonadIO m) => MVector RealWorld r' e -> Array r ix e -> m (MArray RealWorld r' ix e) Source #
Same as unsafeLoadIntoS
, but respecting computation strategy.
Since: 0.5.7
:: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) | |
=> Comp | Computation strategy to use after |
-> Sz ix | Size of the newly created array |
-> (Scheduler RealWorld a -> MArray RealWorld r ix e -> m b) | An action that should fill all elements of the brand new mutable array |
-> m ([a], Array r ix e) |
Same as createArray
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
:: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) | |
=> Comp | Computation strategy to use after |
-> Sz ix | Size of the newly created array |
-> (Scheduler RealWorld a -> MArray RealWorld r ix e -> m b) | An action that should fill all elements of the brand new mutable array |
-> m (Array r ix e) |
Same as createArray_
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) | |
=> Sz ix | Size of the newly created array |
-> (MArray (PrimState m) r ix e -> m a) | An action that should fill all elements of the brand new mutable array |
-> m (a, Array r ix e) |
Same as createArrayS
, but memory will not be initialized
and for unboxed types might contain garbage.
Since: 0.5.0
Read
unsafeRead :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e Source #
Read an array element
Since: 0.1.0
unsafeLinearRead :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> m e Source #
Read an element at linear row-major index
Since: 0.1.0
Write
unsafeWrite :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #
Write an element into array
Since: 0.1.0
unsafeLinearWrite :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> e -> m () Source #
Write an element into mutable array with linear row-major index
Since: 0.1.0
Modify
unsafeModify :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> ix -> m e Source #
Modify an element in the array with a monadic action. Returns the previous value.
Since: 0.4.0
unsafeLinearModify :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> Int -> m e Source #
Modify an element in the array with a monadic action. Returns the previous value.
Since: 0.4.0
Swap
unsafeSwap :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m (e, e) Source #
Swap two elements in a mutable array under the supplied indices. Returns the previous values.
Since: 0.4.0
unsafeLinearSwap :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Int -> Int -> m (e, e) Source #
Swap two elements in a mutable array under the supplied linear indices. Returns the previous values.
Since: 0.4.0
Range modification
unsafeLinearSet :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Ix1 -> Sz1 -> e -> m () Source #
Set all cells in the mutable array within the range to a specified value.
Since: 0.3.0
:: Manifest r e | |
=> (Index ix', Index ix, PrimMonad m) | |
=> MArray (PrimState m) r ix' e | Source mutable array |
-> Ix1 | Starting index at source array |
-> MArray (PrimState m) r ix e | Target mutable array |
-> Ix1 | Starting index at target array |
-> Sz1 | Number of elements to copy |
-> m () |
Copy part of one mutable array into another
Since: 0.3.6
unsafeArrayLinearCopy Source #
:: Manifest r e | |
=> (Index ix', Index ix, PrimMonad m) | |
=> Array r ix' e | Source pure array |
-> Ix1 | Starting index at source array |
-> MArray (PrimState m) r ix e | Target mutable array |
-> Ix1 | Starting index at target array |
-> Sz1 | Number of elements to copy |
-> m () |
Copy a part of a pure array into a mutable array
Since: 0.3.6
Resizing
unsafeLinearShrink :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e) Source #
Linearly reduce the size of an array. Total number of elements should be smaller or equal. There is no guarantee that the original array is left unchanged, so it should no longer be used.
Since: 0.3.6
unsafeLinearGrow :: Manifest r e => (Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> Sz ix -> m (MArray (PrimState m) r ix e) Source #
Linearly increase the size of an array. Total number of elements should be larger or equal. There is no guarantee that the original array is left unchanged, so it should no longer be used.
Since: 0.3.6
Pointer access
unsafeMallocMArray :: forall ix e m. (Index ix, Storable e, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e) Source #
Allocate memory using malloc
on C heap, instead of on Haskell heap. Memory is left
uninitialized
Since: 0.5.9
unsafeWithPtr :: MonadUnliftIO m => Array S ix e -> (Ptr e -> m b) -> m b Source #
A pointer to the beginning of the storable array. It is unsafe since, if mutated, it can break referential transparency.
Since: 0.1.3
unsafeArrayToForeignPtr :: Index ix => Array S ix e -> (ForeignPtr e, Int) Source #
O(1) - Yield the underlying ForeignPtr
together with its length.
Since: 0.3.0
unsafeMArrayToForeignPtr :: Index ix => MArray s S ix e -> (ForeignPtr e, Int) Source #
O(1) - Yield the underlying ForeignPtr
together with its length.
Since: 0.3.0
unsafeArrayFromForeignPtr :: Storable e => Comp -> ForeignPtr e -> Int -> Sz1 -> Array S Ix1 e Source #
O(1) - Wrap a ForeignPtr
, an offset and it's size into a pure storable array.
Since: 0.3.0
unsafeArrayFromForeignPtr0 :: Comp -> ForeignPtr e -> Sz1 -> Vector S e Source #
O(1) - Wrap a ForeignPtr
and it's size into a pure storable array.
Since: 0.3.0
unsafeMArrayFromForeignPtr :: Storable e => ForeignPtr e -> Int -> Sz1 -> MArray s S Ix1 e Source #
O(1) - Wrap a ForeignPtr
, an offset and it's size into a mutable storable array. It is
still safe to modify the pointer, unless the array gets frozen prior to modification.
Since: 0.3.0
unsafeMArrayFromForeignPtr0 :: ForeignPtr e -> Sz1 -> MArray s S Ix1 e Source #
O(1) - Wrap a ForeignPtr
and it's size into a mutable storable array. It is still safe to
modify the pointer, unless the array gets frozen prior to modification.
Since: 0.3.0
Atomic Operations
unsafeAtomicReadIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> m Int Source #
Atomically read an Int
element from the array
Since: 0.3.0
unsafeAtomicWriteIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m () Source #
Atomically write an Int
element int the array
Since: 0.3.0
unsafeAtomicModifyIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> (Int -> Int) -> m Int Source #
Atomically modify an Int
element of the array. Returns the old value.
Since: 0.3.0
unsafeAtomicAddIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically add to an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicSubIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically subtract from an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicAndIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically AND an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicNandIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically NAND an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicOrIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically OR an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeAtomicXorIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> m Int Source #
Atomically XOR an Int
element in the array. Returns the old value.
Since: 0.3.0
unsafeCasIntArray :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix Int -> ix -> Int -> Int -> m Int Source #
Atomically CAS an Int
in the array. Returns the old value.
Since: 0.3.0
Other operations
coerceBoxedArray :: Array BL ix e -> Array B ix e Source #
O(1) - Cast a boxed lazy array. It is unsafe because it can violate the invariant
that all elements of B
array are in WHNF.
Since: 0.6.0
coerceNormalBoxedArray :: Array BL ix e -> Array N ix e Source #
O(1) - Cast a boxed lazy array. It is unsafe because it can violate the invariant
that all elements of N
array are in NF.
Since: 0.6.0
unsafeUnstablePartitionRegionM Source #
:: forall r e m. (Manifest r e, PrimMonad m) | |
=> MVector (PrimState m) r e | |
-> (e -> m Bool) | |
-> Ix1 | Start index of the region |
-> Ix1 | End index of the region |
-> m Ix1 |
Partition a segment of a vector. Starting and ending indices are unchecked.
Since: 1.0.0
Vector
Accessors
Indexing
unsafeHead :: Source r e => Vector r e -> e Source #
Since: 0.5.0
unsafeLast :: Source r e => Vector r e -> e Source #
Since: 0.5.0
Monadic Indexing
Slicing
Unbounded streams
:: 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.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of when unfolding function returns a
Nothing
. Supplying n
that is too big will result in an asynchronous
HeapOverflow
exception.
Since: 0.5.1
unsafeUnfoldrNM :: Monad m => Sz1 -> (s -> m (Maybe (e, s))) -> s -> m (Vector DS e) Source #
O(n) - Same as unsafeUnfoldrN
, but with monadic generating function.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of when unfolding function returns a
Nothing
. Supplying n
that is too big will result in an asynchronous
HeapOverflow
exception.
Since: 0.5.1
unsafeFromListN :: Sz1 -> [e] -> Vector DS e Source #
O(n) - Convert a list of a known length to a delayed stream vector.
Unsafe - This function is unsafe because it will allocate enough space in memory for
n
elements ahead of time, regardless of the actual size of the list. Supplying n
that is too big will result in an asynchronous HeapOverflow
exception.
Since: 0.5.1
Stencil
:: Index ix | |
=> Sz ix | Size of the stencil |
-> ix | Center of the stencil |
-> (ix -> (ix -> e) -> a) | Stencil function. |
-> Stencil ix e a |
Similar to makeStencil
, but there are no guarantees that the
stencil will not read out of bounds memory. This stencil is also a bit more powerful in sense it
gets an extra peice of information, namely the exact index for the element it is constructing.
Since: 0.3.0
makeUnsafeConvolutionStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #
Same as makeConvolutionStencil
, but will result in
reading memory out of bounds and potential segfaults if supplied arguments are not valid.
Since: 0.6.0
makeUnsafeCorrelationStencil :: (Index ix, Num e) => Sz ix -> ix -> ((ix -> e -> e -> e) -> e -> e) -> Stencil ix e e Source #
Same as makeCorrelationStencil
, but will result in
reading memory out of bounds and potential segfaults if supplied arguments are not
valid.
Since: 0.6.0
unsafeTransformStencil Source #
:: (Sz ix' -> Sz ix) | Forward modifier for the size |
-> (ix' -> ix) | Forward index modifier |
-> (((ix' -> e) -> (ix' -> e) -> ix' -> a) -> (ix -> e) -> (ix -> e) -> ix -> a) | Inverse stencil function modifier |
-> Stencil ix' e a | Original stencil. |
-> Stencil ix e a |
Perform an arbitrary transformation of a stencil. This stencil modifier can be used for example to turn a vector stencil into a matrix stencil implement, or transpose a matrix stencil. It is really easy to get this wrong, so be extremely careful.
Examples
Convert a 1D stencil into a row or column 2D stencil:
>>>
import Data.Massiv.Array
>>>
import Data.Massiv.Array.Unsafe
>>>
let arr = compute $ iterateN 3 succ 0 :: Array P Ix2 Int
>>>
arr
Array P Seq (Sz (3 :. 3)) [ [ 1, 2, 3 ] , [ 4, 5, 6 ] , [ 7, 8, 9 ] ]>>>
let rowStencil = unsafeTransformStencil (\(Sz n) -> Sz (1 :. n)) (0 :.) $ \ f uget getVal (i :. j) -> f (uget . (i :.)) (getVal . (i :.)) j
>>>
applyStencil noPadding (rowStencil (sumStencil (Sz1 3))) arr
Array DW Seq (Sz (3 :. 1)) [ [ 6 ] , [ 15 ] , [ 24 ] ]>>>
let columnStencil = unsafeTransformStencil (\(Sz n) -> Sz (n :. 1)) (:. 0) $ \ f uget getVal (i :. j) -> f (uget . (:. j)) (getVal . (:. j)) i
>>>
applyStencil noPadding (columnStencil (sumStencil (Sz1 3))) arr
Array DW Seq (Sz (1 :. 3)) [ [ 12, 15, 18 ] ]
Since: 0.5.4
Constructors
data family Array r ix e :: Type Source #
The array family. Representations r
describe how data is arranged or computed. All
arrays have a common property that each index ix
always maps to the same unique
element e
, even if that element does not yet exist in memory and the array has to be
computed in order to get the value of that element. Data is always arranged in a nested
row-major fashion. Rank of an array is specified by
.Dimensions
ix
Since: 0.1.0
Instances
Index ix => Foldable (Array DI ix) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved fold :: Monoid m => Array DI ix m -> m # foldMap :: Monoid m => (a -> m) -> Array DI ix a -> m # foldMap' :: Monoid m => (a -> m) -> Array DI ix a -> m # foldr :: (a -> b -> b) -> b -> Array DI ix a -> b # foldr' :: (a -> b -> b) -> b -> Array DI ix a -> b # foldl :: (b -> a -> b) -> b -> Array DI ix a -> b # foldl' :: (b -> a -> b) -> b -> Array DI ix a -> b # foldr1 :: (a -> a -> a) -> Array DI ix a -> a # foldl1 :: (a -> a -> a) -> Array DI ix a -> a # toList :: Array DI ix a -> [a] # null :: Array DI ix a -> Bool # length :: Array DI ix a -> Int # elem :: Eq a => a -> Array DI ix a -> Bool # maximum :: Ord a => Array DI ix a -> a # minimum :: Ord a => Array DI ix a -> a # | |
Index ix => Foldable (Array D ix) Source # | Row-major sequential folding over a Delayed array. |
Defined in Data.Massiv.Array.Delayed.Pull fold :: Monoid m => Array D ix m -> m # foldMap :: Monoid m => (a -> m) -> Array D ix a -> m # foldMap' :: Monoid m => (a -> m) -> Array D ix a -> m # foldr :: (a -> b -> b) -> b -> Array D ix a -> b # foldr' :: (a -> b -> b) -> b -> Array D ix a -> b # foldl :: (b -> a -> b) -> b -> Array D ix a -> b # foldl' :: (b -> a -> b) -> b -> Array D ix a -> b # foldr1 :: (a -> a -> a) -> Array D ix a -> a # foldl1 :: (a -> a -> a) -> Array D ix a -> a # toList :: Array D ix a -> [a] # null :: Array D ix a -> Bool # length :: Array D ix a -> Int # elem :: Eq a => a -> Array D ix a -> Bool # maximum :: Ord a => Array D ix a -> a # minimum :: Ord a => Array D ix a -> a # | |
Foldable (Array DS Ix1) Source # | |
Defined in Data.Massiv.Array.Delayed.Stream fold :: Monoid m => Array DS Ix1 m -> m # foldMap :: Monoid m => (a -> m) -> Array DS Ix1 a -> m # foldMap' :: Monoid m => (a -> m) -> Array DS Ix1 a -> m # foldr :: (a -> b -> b) -> b -> Array DS Ix1 a -> b # foldr' :: (a -> b -> b) -> b -> Array DS Ix1 a -> b # foldl :: (b -> a -> b) -> b -> Array DS Ix1 a -> b # foldl' :: (b -> a -> b) -> b -> Array DS Ix1 a -> b # foldr1 :: (a -> a -> a) -> Array DS Ix1 a -> a # foldl1 :: (a -> a -> a) -> Array DS Ix1 a -> a # toList :: Array DS Ix1 a -> [a] # null :: Array DS Ix1 a -> Bool # length :: Array DS Ix1 a -> Int # elem :: Eq a => a -> Array DS Ix1 a -> Bool # maximum :: Ord a => Array DS Ix1 a -> a # minimum :: Ord a => Array DS Ix1 a -> a # | |
Index ix => Foldable (Array B ix) Source # | Row-major sequential folding over a Boxed array. |
Defined in Data.Massiv.Array.Manifest.Boxed fold :: Monoid m => Array B ix m -> m # foldMap :: Monoid m => (a -> m) -> Array B ix a -> m # foldMap' :: Monoid m => (a -> m) -> Array B ix a -> m # foldr :: (a -> b -> b) -> b -> Array B ix a -> b # foldr' :: (a -> b -> b) -> b -> Array B ix a -> b # foldl :: (b -> a -> b) -> b -> Array B ix a -> b # foldl' :: (b -> a -> b) -> b -> Array B ix a -> b # foldr1 :: (a -> a -> a) -> Array B ix a -> a # foldl1 :: (a -> a -> a) -> Array B ix a -> a # toList :: Array B ix a -> [a] # null :: Array B ix a -> Bool # length :: Array B ix a -> Int # elem :: Eq a => a -> Array B ix a -> Bool # maximum :: Ord a => Array B ix a -> a # minimum :: Ord a => Array B ix a -> a # | |
Index ix => Foldable (Array BL ix) Source # | Row-major sequential folding over a Boxed array. |
Defined in Data.Massiv.Array.Manifest.Boxed fold :: Monoid m => Array BL ix m -> m # foldMap :: Monoid m => (a -> m) -> Array BL ix a -> m # foldMap' :: Monoid m => (a -> m) -> Array BL ix a -> m # foldr :: (a -> b -> b) -> b -> Array BL ix a -> b # foldr' :: (a -> b -> b) -> b -> Array BL ix a -> b # foldl :: (b -> a -> b) -> b -> Array BL ix a -> b # foldl' :: (b -> a -> b) -> b -> Array BL ix a -> b # foldr1 :: (a -> a -> a) -> Array BL ix a -> a # foldl1 :: (a -> a -> a) -> Array BL ix a -> a # toList :: Array BL ix a -> [a] # null :: Array BL ix a -> Bool # length :: Array BL ix a -> Int # elem :: Eq a => a -> Array BL ix a -> Bool # maximum :: Ord a => Array BL ix a -> a # minimum :: Ord a => Array BL ix a -> a # | |
Index ix => Traversable (Array B ix) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
Index ix => Traversable (Array BL ix) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
Index ix => Applicative (Array DI ix) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved | |
Index ix => Applicative (Array D ix) Source # | |
Defined in Data.Massiv.Array.Delayed.Pull | |
Applicative (Array DS Ix1) Source # | |
Defined in Data.Massiv.Array.Delayed.Stream | |
Functor (Array DI ix) Source # | |
Functor (Array D ix) Source # | |
Index ix => Functor (Array DL ix) Source # | |
Functor (Array DS Ix1) Source # | |
Functor (Array DW ix) Source # | |
Index ix => Functor (Array B ix) Source # | |
Index ix => Functor (Array BL ix) Source # | |
Monad (Array DS Ix1) Source # | |
Monoid (Array DL Ix1 e) Source # | |
Monoid (Array DS Ix1 e) Source # | |
Semigroup (Array DL Ix1 e) Source # | |
Semigroup (Array DS Ix1 e) Source # | |
IsList (Array DS Ix1 e) Source # | |
(IsList (Array L ix e), Ragged L ix e) => IsList (Array B ix e) Source # | |
(IsList (Array L ix e), Ragged L ix e) => IsList (Array BL ix e) Source # | |
(NFData e, IsList (Array L ix e), Ragged L ix e) => IsList (Array BN ix e) Source # | |
(Prim e, IsList (Array L ix e), Ragged L ix e) => IsList (Array P ix e) Source # | |
(Storable e, IsList (Array L ix e), Ragged L ix e) => IsList (Array S ix e) Source # | |
(Unbox e, IsList (Array L ix e), Ragged L ix e) => IsList (Array U ix e) Source # | |
Coercible (Elt ix e) (ListItem ix e) => IsList (Array L ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array DI ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array D ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array DL ix e) Source # | |
Show e => Show (Array DS Ix1 e) Source # | |
(Ragged L ix e, Load DW ix e, Show e) => Show (Array DW ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array B ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array BL ix e) Source # | |
(Ragged L ix e, Show e, NFData e) => Show (Array BN ix e) Source # | |
(Ragged L ix e, Show e, Prim e) => Show (Array P ix e) Source # | |
(Ragged L ix e, Show e, Storable e) => Show (Array S ix e) Source # | |
(Ragged L ix e, Show e, Unbox e) => Show (Array U ix e) Source # | |
(Ragged L ix e, Show e) => Show (Array L ix e) Source # | |
(Index ix, NFData e) => NFData (Array B ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
(Index ix, NFData e) => NFData (Array BL ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
NFData (Array BN ix e) Source # | O(1) - |
Defined in Data.Massiv.Array.Manifest.Boxed | |
Index ix => NFData (Array P ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Primitive | |
NFData ix => NFData (Array S ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Storable | |
NFData ix => NFData (Array U ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Unboxed | |
(Index ix, Eq e) => Eq (Array DI ix e) Source # | |
(Eq e, Index ix) => Eq (Array D ix e) Source # | |
(Index ix, Eq e) => Eq (Array B ix e) Source # | |
(Index ix, Eq e) => Eq (Array BL ix e) Source # | |
(Index ix, NFData e, Eq e) => Eq (Array BN ix e) Source # | |
(Prim e, Eq e, Index ix) => Eq (Array P ix e) Source # | |
(Storable e, Eq e, Index ix) => Eq (Array S ix e) Source # | |
(Unbox e, Eq e, Index ix) => Eq (Array U ix e) Source # | |
(Index ix, Ord e) => Ord (Array DI ix e) Source # | |
Defined in Data.Massiv.Array.Delayed.Interleaved compare :: Array DI ix e -> Array DI ix e -> Ordering # (<) :: Array DI ix e -> Array DI ix e -> Bool # (<=) :: Array DI ix e -> Array DI ix e -> Bool # (>) :: Array DI ix e -> Array DI ix e -> Bool # (>=) :: Array DI ix e -> Array DI ix e -> Bool # | |
(Ord e, Index ix) => Ord (Array D ix e) Source # | |
Defined in Data.Massiv.Array.Delayed.Pull | |
(Index ix, Ord e) => Ord (Array B ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
(Index ix, Ord e) => Ord (Array BL ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed compare :: Array BL ix e -> Array BL ix e -> Ordering # (<) :: Array BL ix e -> Array BL ix e -> Bool # (<=) :: Array BL ix e -> Array BL ix e -> Bool # (>) :: Array BL ix e -> Array BL ix e -> Bool # (>=) :: Array BL ix e -> Array BL ix e -> Bool # | |
(Index ix, NFData e, Ord e) => Ord (Array BN ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed compare :: Array BN ix e -> Array BN ix e -> Ordering # (<) :: Array BN ix e -> Array BN ix e -> Bool # (<=) :: Array BN ix e -> Array BN ix e -> Bool # (>) :: Array BN ix e -> Array BN ix e -> Bool # (>=) :: Array BN ix e -> Array BN ix e -> Bool # | |
(Prim e, Ord e, Index ix) => Ord (Array P ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Primitive | |
(Storable e, Ord e, Index ix) => Ord (Array S ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Storable | |
(Unbox e, Ord e, Index ix) => Ord (Array U ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Unboxed | |
newtype Array DI ix e Source # | |
data Array D ix e Source # | |
Defined in Data.Massiv.Array.Delayed.Pull | |
data Array DL ix e Source # | |
data Array DW ix e Source # | |
newtype Array B ix e Source # | |
data Array BL ix e Source # | |
newtype Array BN ix e Source # | |
data Array P ix e Source # | |
data Array S ix e Source # | |
Defined in Data.Massiv.Array.Manifest.Storable | |
data Array U ix e Source # | |
data Array L ix e Source # | |
newtype Array DS Ix1 e Source # | |
type Item (Array DS Ix1 e) Source # | |
Defined in Data.Massiv.Array.Delayed.Stream | |
type Item (Array B ix e) Source # | |
type Item (Array BL ix e) Source # | |
type Item (Array BN ix e) Source # | |
type Item (Array P ix e) Source # | |
type Item (Array S ix e) Source # | |
type Item (Array U ix e) Source # | |
type Item (Array L ix e) Source # | |
Defined in Data.Massiv.Core.List |
data family MArray s r ix e :: Type Source #
Mutable version of a Manifest
Array
. The extra type argument s
is for
the state token used by IO
and ST
.
Since: 0.1.0
Instances
NFData ix => NFData (MArray s P ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Primitive | |
NFData ix => NFData (MArray s S ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Storable | |
NFData ix => NFData (MArray s U ix e) Source # | |
Defined in Data.Massiv.Array.Manifest.Unboxed | |
newtype MArray s B ix e Source # | |
data MArray s BL ix e Source # | |
Defined in Data.Massiv.Array.Manifest.Boxed | |
newtype MArray s BN ix e Source # | |
data MArray s P ix e Source # | |
Defined in Data.Massiv.Array.Manifest.Primitive | |
data MArray s S ix e Source # | |
Defined in Data.Massiv.Array.Manifest.Storable | |
data MArray s U ix e Source # | |