massiv-1.0.0.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2021
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Mutable

Description

 
Synopsis

Size

sizeOfMArray :: (Manifest r e, Index ix) => MArray s r ix e -> Sz ix Source #

O(1) - Get the size of a mutable array.

Since: 1.0.0

msize :: (Manifest r e, Index ix) => MArray s r ix e -> Sz ix Source #

Deprecated: In favor of sizeOfMArray

Get the size of a mutable array.

Since: 0.1.0

resizeMArrayM :: (Manifest r e, Index ix', Index ix, MonadThrow m) => Sz ix' -> MArray s r ix e -> m (MArray s r ix' e) Source #

O(1) - Change the size of a mutable array. Throws SizeElementsMismatchException if total number of elements does not match the supplied array.

Since: 1.0.0

flattenMArray :: (Manifest r e, Index ix) => MArray s r ix e -> MVector s r e Source #

O(1) - Change a mutable array to a mutable vector.

Since: 1.0.0

outerSliceMArrayM :: forall r ix e m s. (MonadThrow m, Index (Lower ix), Index ix, Manifest r e) => MArray s r ix e -> Ix1 -> m (MArray s r (Lower ix) e) Source #

O(1) - Slice a mutable array from the outside, while reducing its dimensionality by one. Same as !?> operator, but for mutable arrays.

Since: 1.0.0

outerSlicesMArray :: forall r ix e s. (Index (Lower ix), Index ix, Manifest r e) => Comp -> MArray s r ix e -> Vector D (MArray s r (Lower ix) e) Source #

O(1) - Take all outer slices of a mutable array and construct a delayed vector out of them. In other words it applies outerSliceMArrayM to each outer index. Same as outerSlices function, but for mutable arrays.

Examples

Expand
>>> import Data.Massiv.Array as A
>>> arr <- resizeM (Sz2 4 7) $ makeArrayR P Seq (Sz1 28) (+10)
>>> arr
Array P Seq (Sz (4 :. 7))
  [ [ 10, 11, 12, 13, 14, 15, 16 ]
  , [ 17, 18, 19, 20, 21, 22, 23 ]
  , [ 24, 25, 26, 27, 28, 29, 30 ]
  , [ 31, 32, 33, 34, 35, 36, 37 ]
  ]

Here we can see we can get individual rows from a mutable matrix

>>> marr <- thawS arr
>>> import Control.Monad ((<=<))
>>> mapIO_ (print <=< freezeS)  $ outerSlicesMArray Seq marr
Array P Seq (Sz1 7)
  [ 10, 11, 12, 13, 14, 15, 16 ]
Array P Seq (Sz1 7)
  [ 17, 18, 19, 20, 21, 22, 23 ]
Array P Seq (Sz1 7)
  [ 24, 25, 26, 27, 28, 29, 30 ]
Array P Seq (Sz1 7)
  [ 31, 32, 33, 34, 35, 36, 37 ]

For the sake of example what if our goal was to mutate array in such a way that rows from the top half were swapped with the bottom half:

>>> (top, bottom) <- splitAtM 1 2 $ outerSlicesMArray Seq marr
>>> mapIO_ (print <=< freezeS) top
Array P Seq (Sz1 7)
  [ 10, 11, 12, 13, 14, 15, 16 ]
Array P Seq (Sz1 7)
  [ 17, 18, 19, 20, 21, 22, 23 ]
>>> mapIO_ (print <=< freezeS) bottom
Array P Seq (Sz1 7)
  [ 24, 25, 26, 27, 28, 29, 30 ]
Array P Seq (Sz1 7)
  [ 31, 32, 33, 34, 35, 36, 37 ]
>>> szipWithM_ (zipSwapM_ 0) top bottom
>>> freezeS marr
Array P Seq (Sz (4 :. 7))
  [ [ 24, 25, 26, 27, 28, 29, 30 ]
  , [ 31, 32, 33, 34, 35, 36, 37 ]
  , [ 10, 11, 12, 13, 14, 15, 16 ]
  , [ 17, 18, 19, 20, 21, 22, 23 ]
  ]

Since: 1.0.0

Element-wise mutation

read :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m (Maybe e) Source #

O(1) - Lookup an element in the mutable array. Returns Nothing when index is out of bounds.

Since: 0.1.0

readM :: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) => MArray (PrimState m) r ix e -> ix -> m e Source #

O(1) - Same as read, but throws IndexOutOfBoundsException on an invalid index.

Since: 0.4.0

write :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m Bool Source #

O(1) - Write an element into the cell of a mutable array. Returns False when index is out of bounds.

Since: 0.1.0

write_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

O(1) - Write an element into the cell of a mutable array. Same as write function in case of an out of bounds index it is noop, but unlike write, there is no information is returned about was the writing of element successful or not. In other words, just like writeM, but doesn't throw an exception.

Since: 0.4.4

writeM :: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

O(1) - Same as write, but throws IndexOutOfBoundsException on an invalid index.

Since: 0.4.0

modify Source #

Arguments

:: (Manifest r e, Index ix, PrimMonad m) 
=> MArray (PrimState m) r ix e

Array to mutate.

-> (e -> m e)

Monadic action that modifies the element

-> ix

Index at which to perform modification.

-> m (Maybe e) 

O(1) - Modify an element in the cell of a mutable array with a supplied action. Returns the previous value, if index was not out of bounds.

Since: 0.1.0

modify_ Source #

Arguments

:: (Manifest r e, Index ix, PrimMonad m) 
=> MArray (PrimState m) r ix e

Array to mutate.

-> (e -> m e)

Monadic action that modifies the element

-> ix

Index at which to perform modification.

-> m () 

O(1) - Same as modify, except that neither the previous value, nor any information on whether the modification was successful are returned. In other words, just like modifyM_, but doesn't throw an exception.

Since: 0.4.4

modifyM Source #

Arguments

:: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) 
=> MArray (PrimState m) r ix e

Array to mutate.

-> (e -> m e)

Monadic action that modifies the element

-> ix

Index at which to perform modification.

-> m e 

O(1) - Modify an element in the cell of a mutable array with a supplied action. Throws an IndexOutOfBoundsException exception for invalid index and returns the previous value otherwise.

Since: 0.4.0

modifyM_ Source #

Arguments

:: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) 
=> MArray (PrimState m) r ix e

Array to mutate.

-> (e -> m e)

Monadic action that modifies the element

-> ix

Index at which to perform modification.

-> m () 

O(1) - Same as modifyM, but discard the returned element

Examples

Expand
>>> :set -XTypeApplications
>>> import Control.Monad.ST
>>> import Data.Massiv.Array
>>> runST $ newMArray' @P @Ix1 @Int (Sz1 3) >>= (\ma -> modifyM_ ma (pure . (+10)) 1 >> freezeS ma)
Array P Seq (Sz1 3)
  [ 0, 10, 0 ]

Since: 0.4.0

swap :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m (Maybe (e, e)) Source #

O(1) - Same as swapM, but instead of throwing an exception returns Nothing when either one of the indices is out of bounds and Just elements under those indices otherwise.

Since: 0.1.0

swap_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m () Source #

O(1) - Same as swap, but instead of returning Nothing it does nothing. In other words, it is similar to swapM_, but does not throw any exceptions.

Since: 0.4.4

swapM Source #

Arguments

:: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) 
=> MArray (PrimState m) r ix e 
-> ix

Index for the first element, which will be returned as the first element in the tuple.

-> ix

Index for the second element, which will be returned as the second element in the tuple.

-> m (e, e) 

O(1) - Swap two elements in a mutable array under the supplied indices. Throws an IndexOutOfBoundsException when either one of the indices is out of bounds and elements under those indices otherwise.

Since: 0.4.0

swapM_ :: (Manifest r e, Index ix, PrimMonad m, MonadThrow m) => MArray (PrimState m) r ix e -> ix -> ix -> m () Source #

O(1) - Same as swapM, but discard the returned elements

Since: 0.4.0

zipSwapM_ :: forall r1 r2 ix e m s. (MonadPrim s m, Manifest r2 e, Manifest r1 e, Index ix) => ix -> MArray s r1 ix e -> MArray s r2 ix e -> m () Source #

Swap elements in the intersection of two mutable arrays starting at the initial index.

Since: 1.0.0

Operations on MArray

Immutable conversion

thaw :: forall r ix e m. (Manifest r e, Index ix, MonadIO m) => Array r ix e -> m (MArray RealWorld r ix e) Source #

O(n) - Make a mutable copy of a pure array. Keep in mind that both freeze and thaw trigger a copy of the full array.

Example

Expand
>>> import Data.Massiv.Array
>>> :set -XTypeApplications
>>> arr <- fromListsM @U @Ix2 @Double Par [[12,21],[13,31]]
>>> marr <- thaw arr
>>> modify marr (pure . (+ 10)) (1 :. 0)
Just 13.0
>>> freeze Par marr
Array U Par (Sz (2 :. 2))
  [ [ 12.0, 21.0 ]
  , [ 23.0, 31.0 ]
  ]

Since: 0.1.0

thawS :: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) => Array r ix e -> m (MArray (PrimState m) r ix e) Source #

Same as thaw, but restrict computation to sequential only.

Example

Expand
>>> import Data.Massiv.Array
>>> :set -XOverloadedLists
>>> thawS @P @Ix1 @Double [1..10]
>>> marr <- thawS @P @Ix1 @Double [1..10]
>>> writeM marr 5 100
>>> freezeS marr
Array P Seq (Sz1 10)
  [ 1.0, 2.0, 3.0, 4.0, 5.0, 100.0, 7.0, 8.0, 9.0, 10.0 ]

Since: 0.3.0

freeze :: forall r ix e m. (Manifest r e, Index ix, MonadIO m) => Comp -> MArray RealWorld r ix e -> m (Array r ix e) Source #

O(n) - Yield an immutable copy of the mutable array. Note that mutable representations have to be the same.

Example

Expand
>>> import Data.Massiv.Array
>>> marr <- newMArray @P (Sz2 2 6) (0 :: Int)
>>> forM_ (range Seq 0 (Ix2 1 4)) $ \ix -> write marr ix 9
>>> freeze Seq marr
Array P Seq (Sz (2 :. 6))
  [ [ 9, 9, 9, 9, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0 ]
  ]

Since: 0.1.0

freezeS :: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> m (Array r ix e) Source #

Same as freeze, but do the copy of supplied muable array sequentially. Also, unlike freeze that has to be done in IO, freezeS can be used with ST.

Since: 0.3.0

Create mutable

newMArray :: (Manifest r e, Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) r ix e) Source #

Create new mutable array while initializing all elements to the specified value.

Since: 0.6.0

newMArray' :: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) r ix e) Source #

O(n) - Initialize a new mutable array. All elements will be set to some default value. For boxed arrays it will be a thunk with Uninitialized exception, while for others it will be simply zeros.

Examples

Expand
>>> import Data.Massiv.Array
>>> marr <- newMArray' (Sz2 2 6) :: IO (MArray RealWorld P Ix2 Int)
>>> freeze Seq marr
Array P Seq (Sz (2 :. 6))
  [ [ 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0 ]
  ]

Or using TypeApplications:

>>> :set -XTypeApplications
>>> newMArray' @P @Ix2 @Int (Sz2 2 6) >>= freezeS
Array P Seq (Sz (2 :. 6))
  [ [ 0, 0, 0, 0, 0, 0 ]
  , [ 0, 0, 0, 0, 0, 0 ]
  ]
>>> newMArray' @B @_ @Int (Sz2 2 6) >>= freezeS
*** Exception: Uninitialized

Since: 0.6.0

makeMArray :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (ix -> m e) -> m (MArray RealWorld r ix e) Source #

Just like makeMArrayS, but also accepts computation strategy and runs in IO.

Since: 0.3.0

makeMArrayLinear :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (Int -> m e) -> m (MArray RealWorld r ix e) Source #

Just like makeMArrayLinearS, but also accepts computation strategy and runs in IO.

Since: 0.3.0

makeMArrayS Source #

Arguments

:: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the create array

-> (ix -> m e)

Element generating action

-> m (MArray (PrimState m) r ix e) 

Create a mutable array using an index aware generating action.

Since: 0.3.0

makeMArrayLinearS :: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) => Sz ix -> (Int -> m e) -> m (MArray (PrimState m) r ix e) Source #

Same as makeMArrayS, but index supplied to the action is row-major linear index.

Since: 0.3.0

Create pure

createArray_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> Sz ix

Size of the newly created array

-> (Scheduler RealWorld () -> MArray RealWorld r ix e -> m a)

An action that should fill all elements of the brand new mutable array

-> m (Array r ix e) 

Create a new array by supplying an action that will fill the new blank mutable array. Use createArray if you'd like to keep the result of the filling function.

Examples

Expand
>>> :set -XTypeApplications
>>> import Data.Massiv.Array
>>> createArray_ @P @_ @Int Seq (Sz1 2) (\ s marr -> scheduleWork s (writeM marr 0 10) >> scheduleWork s (writeM marr 1 11))
Array P Seq (Sz1 2)
  [ 10, 11 ]

Since: 0.3.0

createArray Source #

Arguments

:: forall r ix e a m b. (Manifest r e, Index ix, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> 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) 

Just like createArray_, but together with Array it returns results of scheduled filling actions.

Since: 0.3.0

createArrayS_ Source #

Arguments

:: 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 (Array r ix e) 

Create a new array by supplying an action that will fill the new blank mutable array. Use createArrayS if you'd like to keep the result of the filling function.

Examples

Expand
>>> :set -XTypeApplications
>>> import Data.Massiv.Array
>>> createArrayS_ @P @_ @Int (Sz1 2) (\ marr -> write marr 0 10 >> write marr 1 12)
Array P Seq (Sz1 2)
  [ 10, 12 ]

Since: 0.3.0

createArrayS Source #

Arguments

:: 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) 

Just like createArray_, but together with Array it returns the result of the filling action.

Since: 0.3.0

createArrayST_ :: forall r ix e a. (Manifest r e, Index ix) => Sz ix -> (forall s. MArray s r ix e -> ST s a) -> Array r ix e Source #

Just like createArrayS_, but restricted to ST.

Since: 0.3.0

createArrayST :: forall r ix e a. (Manifest r e, Index ix) => Sz ix -> (forall s. MArray s r ix e -> ST s a) -> (a, Array r ix e) Source #

Just like createArrayS, but restricted to ST.

Since: 0.2.6

Generate

generateArray :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (ix -> m e) -> m (Array r ix e) Source #

Just like generateArrayS, except this generator will respect the supplied computation strategy, and for that reason it is restricted to IO.

Since: 0.2.6

generateArrayLinear :: forall r ix e m. (MonadUnliftIO m, Manifest r e, Index ix) => Comp -> Sz ix -> (Int -> m e) -> m (Array r ix e) Source #

Just like generateArray, except generating action will receive a row-major linear index.

Since: 0.3.0

generateArrayS Source #

Arguments

:: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Resulting size of the array

-> (ix -> m e)

Element producing generator

-> m (Array r ix e) 

Sequentially generate a pure array. Much like makeArray creates a pure array this function will use Manifest interface to generate a pure Array in the end, except that computation strategy is set to Seq. Element producing function no longer has to be pure but is a stateful action, becuase it is restricted to PrimMonad thus allows for sharing the state between computation of each element.

Examples

Expand
>>> import Data.Massiv.Array
>>> import Data.IORef
>>> ref <- newIORef (0 :: Int)
>>> generateArrayS (Sz1 6) (\ i -> modifyIORef' ref (+i) >> print i >> pure i) :: IO (Array U Ix1 Int)
0
1
2
3
4
5
Array U Seq (Sz1 6)
  [ 0, 1, 2, 3, 4, 5 ]
>>> readIORef ref
15

Since: 0.2.6

generateArrayLinearS Source #

Arguments

:: forall r ix e m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Resulting size of the array

-> (Int -> m e)

Element producing generator

-> m (Array r ix e) 

Same as generateArray but with action that accepts row-major linear index.

Since: 0.3.0

Stateful worker threads

generateArrayWS :: forall r ix e s m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Sz ix -> (ix -> s -> m e) -> m (Array r ix e) Source #

Use per worker thread state while generating elements of the array. Very useful for things that are not thread safe.

Since: 0.3.4

generateArrayLinearWS :: forall r ix e s m. (Manifest r e, Index ix, MonadUnliftIO m, PrimMonad m) => WorkerStates s -> Sz ix -> (Int -> s -> m e) -> m (Array r ix e) Source #

Same as generateArrayWS, but use linear indexing instead.

Since: 0.3.4

Unfold

unfoldrPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Sequentially unfold an array from the left.

Examples

Expand

Create an array with Fibonacci numbers while performing and IO action on the accumulator for each element of the array.

>>> import Data.Massiv.Array
>>> unfoldrPrimM_ (Sz1 10) (\a@(f0, f1) -> let fn = f0 + f1 in print a >> return (f0, (f1, fn))) (0, 1) :: IO (Array P Ix1 Int)
(0,1)
(1,1)
(1,2)
(2,3)
(3,5)
(5,8)
(8,13)
(13,21)
(21,34)
(34,55)
Array P Seq (Sz1 10)
  [ 0, 1, 1, 2, 3, 5, 8, 13, 21, 34 ]

Since: 0.3.0

iunfoldrPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Same as unfoldrPrimM_ but do the unfolding with index aware function.

Since: 0.3.0

unfoldrPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldrPrimM, but do the unfolding with index aware function.

Since: 0.3.0

iunfoldrPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (e, a))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldrPrimM_, but also returns the final value of the accumulator.

Since: 0.3.0

unfoldlPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Sequentially unfold an array from the left.

Examples

Expand

Create an array with Fibonacci numbers starting at the end while performing and IO action on the accumulator for each element of the array.

>>> import Data.Massiv.Array
>>> unfoldlPrimM_ (Sz1 10) (\a@(f0, f1) -> let fn = f0 + f1 in print a >> return ((f1, fn), f0)) (0, 1) :: IO (Array P Ix1 Int)
(0,1)
(1,1)
(1,2)
(2,3)
(3,5)
(5,8)
(8,13)
(13,21)
(21,34)
(34,55)
Array P Seq (Sz1 10)
  [ 34, 21, 13, 8, 5, 3, 2, 1, 1, 0 ]

Since: 0.3.0

iunfoldlPrimM_ Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

Same as unfoldlPrimM_ but do the unfolding with index aware function.

Since: 0.3.0

unfoldlPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldlPrimM, but do the unfolding with index aware function.

Since: 0.3.0

iunfoldlPrimM Source #

Arguments

:: forall r ix e a m. (Manifest r e, Index ix, PrimMonad m) 
=> Sz ix

Size of the desired array

-> (a -> ix -> m (a, e))

Unfolding action

-> a

Initial accumulator

-> m (a, Array r ix e) 

Just like iunfoldlPrimM_, but also returns the final value of the accumulator.

Since: 0.3.0

Mapping

forPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an action.

Since: 0.4.0

forPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying an action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

iforPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (ix -> e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an index aware action.

Since: 0.4.0

iforPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (ix -> e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying an index aware action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

iforLinearPrimM :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (Int -> e -> m e) -> m () Source #

Sequentially loop over a mutable array while modifying each element with an index aware action.

Since: 0.4.0

iforLinearPrimM_ :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> (Int -> e -> m ()) -> m () Source #

Sequentially loop over a mutable array while reading each element and applying a linear index aware action to it. There is no mutation to the array, unless the action itself modifies it.

Since: 0.4.0

for2PrimM_ :: forall r1 r2 e1 e2 ix m. (PrimMonad m, Index ix, Manifest r1 e1, Manifest r2 e2) => MArray (PrimState m) r1 ix e1 -> MArray (PrimState m) r2 ix e2 -> (e1 -> e2 -> m ()) -> m () Source #

Sequentially loop over the intersection of two mutable arrays while reading elements from both and applying an action to it. There is no mutation to the actual arrays, unless the action itself modifies either one of them.

Since: 1.0.0

ifor2PrimM_ :: forall r1 r2 e1 e2 ix m. (PrimMonad m, Index ix, Manifest r1 e1, Manifest r2 e2) => MArray (PrimState m) r1 ix e1 -> MArray (PrimState m) r2 ix e2 -> (ix -> e1 -> e2 -> m ()) -> m () Source #

Same as for2PrimM_, but with index aware action.

Since: 1.0.0

Modify

withMArray :: (Manifest r e, Index ix, MonadUnliftIO m) => Array r ix e -> (Scheduler RealWorld a -> MArray RealWorld r ix e -> m b) -> m ([a], Array r ix e) Source #

Same as withMArray_, but allows to keep artifacts of scheduled tasks.

Since: 0.5.0

withMArray_ :: (Manifest r e, Index ix, MonadUnliftIO m) => Array r ix e -> (Scheduler RealWorld () -> MArray RealWorld r ix e -> m a) -> m (Array r ix e) Source #

Create a copy of a pure array, mutate it in place and return its frozen version. The big difference between withMArrayS is that it's not only gonna respect the computation strategy supplied to it while making a copy, but it will also pass extra argumens to the action that suppose to modify the mutable copy of the source array. These two extra arguments are:

  • Number of capabilities derived from the Computation strategy of the array.
  • An action that can be used to schedule arbitrary number of jobs that will be executed in parallel.
  • And, of course, the mutable array itself.

Since: 0.5.0

withLoadMArray_ :: forall r ix e r' m b. (Load r' ix e, Manifest r e, MonadUnliftIO m) => Array r' ix e -> (Scheduler RealWorld () -> MArray RealWorld r ix e -> m b) -> m (Array r ix e) Source #

Same as withMArray_, but the array supplied to this function can be any loadable array. For that reason it will be faster if supplied array is delayed.

Since: 0.6.1

withMArrayS :: (Manifest r e, Index ix, PrimMonad m) => Array r ix e -> (MArray (PrimState m) r ix e -> m a) -> m (a, Array r ix e) Source #

Create a copy of a pure array, mutate it in place and return its frozen version. The important benefit over doing a manual thawS followed by a freezeS is that an array will only be copied once.

Since: 0.5.0

withLoadMArrayS :: forall r ix e r' m a. (Load r' ix e, Manifest r e, PrimMonad m) => Array r' ix e -> (MArray (PrimState m) r ix e -> m a) -> m (a, Array r ix e) Source #

Same as withMArrayS, but will work with any loadable array.

Since: 0.6.1

withMArrayS_ :: (Manifest r e, Index ix, PrimMonad m) => Array r ix e -> (MArray (PrimState m) r ix e -> m a) -> m (Array r ix e) Source #

Same as withMArrayS, except it discards the value produced by the supplied action

Since: 0.5.0

withLoadMArrayS_ :: forall r ix e r' m a. (Load r' ix e, Manifest r e, PrimMonad m) => Array r' ix e -> (MArray (PrimState m) r ix e -> m a) -> m (Array r ix e) Source #

Same as withMArrayS_, but will work with any loadable array.

Since: 0.6.1

withMArrayST :: (Manifest r e, Index ix) => Array r ix e -> (forall s. MArray s r ix e -> ST s a) -> (a, Array r ix e) Source #

Same as withMArrayS but in ST. This is not only pure, but also the safest way to do mutation to the array.

Since: 0.5.0

withLoadMArrayST :: forall r ix e r' a. (Load r' ix e, Manifest r e) => Array r' ix e -> (forall s. MArray s r ix e -> ST s a) -> (a, Array r ix e) Source #

Same as withMArrayST, but works with any loadable array.

Since: 0.6.1

withMArrayST_ :: (Manifest r e, Index ix) => Array r ix e -> (forall s. MArray s r ix e -> ST s a) -> Array r ix e Source #

Same as withMArrayS but in ST. This is not only pure, but also the safest way to do mutation to the array.

Since: 0.5.0

withLoadMArrayST_ :: forall r ix e r' a. (Load r' ix e, Manifest r e) => Array r' ix e -> (forall s. MArray s r ix e -> ST s a) -> Array r ix e Source #

Same as withMArrayST_, but works with any loadable array.

Since: 0.6.1

Initialize

initialize :: (Manifest r e, Index ix, PrimMonad m) => MArray (PrimState m) r ix e -> m () Source #

Initialize mutable array to some default value.

Since: 0.3.0

initializeNew :: (Manifest r e, Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) r ix e) Source #

Create new mutable array while initializing all elements to some default value.

Since: 0.3.0

Computation

class Source r e => Manifest r e Source #

Manifest arrays are backed by actual memory and values are looked up versus computed as it is with delayed arrays. Because manifest arrays are located in memory their contents can be mutated once thawed into MArray. The process of changed a mutable MArray back into an immutable Array is called freezing.

Instances

Instances details
Unbox e => Manifest U e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

unsafeLinearIndexM :: Index ix => Array U ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s U ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s U ix e -> MArray s U ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s U ix e -> MVector s U e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array U ix e -> m (MArray (PrimState m) U ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) U ix e -> m (Array U ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array U ix' e -> Ix1 -> MArray (PrimState m) U ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) U ix e -> Sz ix -> m (MArray (PrimState m) U ix e) Source #

Storable e => Manifest S e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

unsafeLinearIndexM :: Index ix => Array S ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s S ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s S ix e -> MArray s S ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s S ix e -> MVector s S e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array S ix e -> m (MArray (PrimState m) S ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) S ix e -> m (Array S ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array S ix' e -> Ix1 -> MArray (PrimState m) S ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) S ix e -> Sz ix -> m (MArray (PrimState m) S ix e) Source #

Prim e => Manifest P e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

unsafeLinearIndexM :: Index ix => Array P ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s P ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s P ix e -> MArray s P ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s P ix e -> MVector s P e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array P ix e -> m (MArray (PrimState m) P ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) P ix e -> m (Array P ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array P ix' e -> Ix1 -> MArray (PrimState m) P ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) P ix e -> Sz ix -> m (MArray (PrimState m) P ix e) Source #

NFData e => Manifest BN e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BN ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BN ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s BN ix e -> MArray s BN ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BN ix e -> MVector s BN e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BN ix e -> m (MArray (PrimState m) BN ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BN ix e -> m (Array BN ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BN ix' e -> Ix1 -> MArray (PrimState m) BN ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BN ix e -> Sz ix -> m (MArray (PrimState m) BN ix e) Source #

Manifest B e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array B ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s B ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s B ix e -> MArray s B ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s B ix e -> MVector s B e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array B ix e -> m (MArray (PrimState m) B ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) B ix e -> m (Array B ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array B ix' e -> Ix1 -> MArray (PrimState m) B ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) B ix e -> Sz ix -> m (MArray (PrimState m) B ix e) Source #

Manifest BL e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Methods

unsafeLinearIndexM :: Index ix => Array BL ix e -> Int -> e Source #

sizeOfMArray :: Index ix => MArray s BL ix e -> Sz ix Source #

unsafeResizeMArray :: (Index ix', Index ix) => Sz ix' -> MArray s BL ix e -> MArray s BL ix' e Source #

unsafeLinearSliceMArray :: Index ix => Ix1 -> Sz1 -> MArray s BL ix e -> MVector s BL e Source #

unsafeThaw :: (Index ix, PrimMonad m) => Array BL ix e -> m (MArray (PrimState m) BL ix e) Source #

unsafeFreeze :: (Index ix, PrimMonad m) => Comp -> MArray (PrimState m) BL ix e -> m (Array BL ix e) Source #

unsafeNew :: (Index ix, PrimMonad m) => Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearRead :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> m e Source #

unsafeLinearWrite :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Int -> e -> m () Source #

initialize :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> m () Source #

initializeNew :: (Index ix, PrimMonad m) => Maybe e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

newMArray :: (Index ix, PrimMonad m) => Sz ix -> e -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearSet :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> e -> m () Source #

unsafeLinearCopy :: (Index ix', Index ix, PrimMonad m) => MArray (PrimState m) BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeArrayLinearCopy :: (Index ix', Index ix, PrimMonad m) => Array BL ix' e -> Ix1 -> MArray (PrimState m) BL ix e -> Ix1 -> Sz1 -> m () Source #

unsafeLinearShrink :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

unsafeLinearGrow :: (Index ix, PrimMonad m) => MArray (PrimState m) BL ix e -> Sz ix -> m (MArray (PrimState m) BL ix e) Source #

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

Instances details
NFData ix => NFData (MArray s U ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Methods

rnf :: MArray s U ix e -> () #

NFData ix => NFData (MArray s S ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Methods

rnf :: MArray s S ix e -> () #

NFData ix => NFData (MArray s P ix e) Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Methods

rnf :: MArray s P ix e -> () #

data MArray s U ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

data MArray s U ix e = MUArray !(Sz ix) !(MVector s e)
data MArray s S ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

data MArray s S ix e = MSArray !(Sz ix) !(ForeignPtr e)
data MArray s P ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

data MArray s P ix e = MPArray !(Sz ix) !Int !(MutableByteArray s)
data MArray s BL ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

data MArray s BL ix e = MBLArray !(Sz ix) !Int !(MutableArray s e)
newtype MArray s B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype MArray s B ix e = MBArray (MArray s BL ix e)
newtype MArray s BN ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype MArray s BN ix e = MBNArray (MArray s BL ix e)

data RealWorld #

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

Instances

Instances details
Prim a => Storable (PVar a RealWorld)

poke+peek will result in a new copy of a PVar

Instance details

Defined in Data.Primitive.PVar.Internal

computeInto Source #

Arguments

:: (Size r', Load r' ix' e, Manifest r e, Index ix, MonadIO m) 
=> MArray RealWorld r ix e

Target Array

-> Array r' ix' e

Array to load

-> m () 

Compute an Array while loading the results into the supplied mutable target array. Number of elements for arrays must agree, otherwise SizeElementsMismatchException exception is thrown.

Since: 0.1.3

loadArray :: forall r ix e r' m. (Load r' ix e, Manifest r e, MonadIO m) => Array r' ix e -> m (MArray RealWorld r ix e) Source #

Load a pure array into the newly created mutable array, while respecting computation startegy.

Since: 0.3.0

loadArrayS :: forall r ix e r' m. (Load r' ix e, Manifest r e, PrimMonad m) => Array r' ix e -> m (MArray (PrimState m) r ix e) Source #

Load sequentially a pure array into the newly created mutable array.

Since: 0.3.0