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

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

Data.Massiv.Array.Mutable

Contents

Description

 
Synopsis

Size

msize :: Mutable r ix e => MArray s r ix e -> Sz ix Source #

Get the size of a mutable array.

Since: 0.1.0

Element-wise mutation

read :: (Mutable r ix e, 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.

read' :: (Mutable r ix e, MonadThrow m, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> m e Source #

O(1) - Same as read, but lives in IO and throws IndexOutOfBoundsException on invalid index.

write :: (Mutable r ix e, 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.

write' :: (Mutable r ix e, MonadThrow m, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

O(1) - Same as write, but lives in IO and throws IndexOutOfBoundsException on invalid index.

modify :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> e) -> ix -> m Bool Source #

O(1) - Modify an element in the cell of a mutable array with a supplied function. Returns False when index is out of bounds.

modify' :: (Mutable r ix e, MonadThrow m, PrimMonad m) => MArray (PrimState m) r ix e -> (e -> e) -> ix -> m () Source #

O(1) - Same as modify, but throws an error if index is out of bounds.

swap :: (Mutable r ix e, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m Bool Source #

O(1) - Swap two elements in a mutable array by supplying their indices. Returns False when either one of the indices is out of bounds.

swap' :: (Mutable r ix e, MonadThrow m, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m () Source #

O(1) - Same as swap, but throws an IndexOutOfBoundsException on invalid indices.

Operate over MArray

Immutable conversion

new :: forall r ix e m. (Mutable r ix e, 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 in will be a thunk with Uninitialized exception, while for others it will be simply zeros.

Examples

Expand
>>> import Data.Massiv.Array
>>> marr <- new (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
>>> new @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 ]
  ]
>>> new @B @_ @Int (Sz2 2 6) >>= (`read'` 1)
*** Exception: Uninitialized

Since: 0.1.0

thaw :: forall r ix e m. (Mutable r ix e, 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 (+ 10) (1 :. 0)
True
>>> 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. (Mutable r ix e, 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]
>>> write' 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. (Mutable r ix e, 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 <- new @P @_ @Int (Sz2 2 6)
>>> 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. (Mutable r ix e, 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

makeMArray :: forall r ix e m. (PrimMonad m, MonadUnliftIO m, Mutable r ix e) => Comp -> Sz ix -> (ix -> m e) -> m (MArray (PrimState m) 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. (PrimMonad m, MonadUnliftIO m, Mutable r ix e) => Comp -> Sz ix -> (Int -> m e) -> m (MArray (PrimState m) r ix e) Source #

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

Since: 0.3.0

makeMArrayS Source #

Arguments

:: (Mutable r ix e, 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. (Mutable r ix e, 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

:: (Mutable r ix e, PrimMonad m, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> Sz ix

Size of the newly created array

-> (Scheduler m () -> 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 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 (write' marr 0 10) >> scheduleWork s (write' marr 1 11))
Array P Seq (Sz1 2)
  [ 10, 11 ]

Since: 0.3.0

createArray Source #

Arguments

:: (Mutable r ix e, PrimMonad m, MonadUnliftIO m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> Sz ix

Size of the newly created array

-> (Scheduler m a -> 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 results of scheduled filling actions.

Since: 0.3.0

createArrayS_ Source #

Arguments

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> 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 Seq (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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy to use after MArray gets frozen and onward.

-> 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. Mutable r ix e => Comp -> 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. Mutable r ix e => Comp -> 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, PrimMonad m, Mutable r ix e) => 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, PrimMonad m, Mutable r ix e) => Comp -> Sz ix -> (Int -> m e) -> m (Array r ix e) Source #

Just like generateArrayIO, but action supplied will receive a row-major linear index.

Since: 0.3.0

generateArrayS Source #

Arguments

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ingored during generation)

-> 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 Mutable interface to generate a pure Array in the end, except that computation strategy is ignored. Element producing function no longer has to be pure but is a stateful action, since it is restricted to PrimMonad and allows for sharing the state between computation of each element, which could be arbitrary effects if that monad is IO.

Examples

Expand
>>> import Data.Massiv.Array
>>> import Data.IORef
>>> ref <- newIORef (0 :: Int)
>>> generateArray Seq (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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ingored during generation)

-> Sz ix

Resulting size of the array

-> (Int -> m e)

Element producing generator

-> m (Array r ix e) 

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

Since: 0.3.0

Unfold

unfoldrPrimM_ Source #

Arguments

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

-> 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_ Seq  (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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

-> Sz ix

Size of the desired array

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

Unfolding action

-> a

Initial accumulator

-> m (Array r ix e) 

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

Since: 0.3.0

unfoldrPrimM Source #

Arguments

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

-> 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 iunfoldrPrim_, but also returns the final value of the accumulator.

Since: 0.3.0

unfoldlPrimM_ Source #

Arguments

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

-> 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_ Seq  (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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

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

:: (Mutable r ix e, PrimMonad m) 
=> Comp

Computation strategy (ignored during initial creation)

-> 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_ :: (Mutable r ix e, 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.3.0

iforPrimM_ :: (Mutable r ix e, 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.3.0

iforLinearPrimM_ :: (Mutable r ix e, 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.3.0

Modify

withMArray :: (Mutable r ix e, MonadUnliftIO m) => Array r ix e -> (Int -> (m () -> m ()) -> 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, 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.3.0

withMArrayST :: Mutable r ix e => 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.2.2

Initialize

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

Initialize mutable array to some default value.

Since: 0.3.0

initializeNew :: (Mutable r ix e, 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 Manifest r ix e => Mutable r ix e Source #

Instances
(Unbox e, Index ix) => Mutable U ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Unboxed

Associated Types

data MArray s U ix e :: Type Source #

Methods

msize :: MArray s U ix e -> Sz ix Source #

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

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

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

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

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

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

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

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

(Index ix, Storable e) => Mutable S ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Storable

Associated Types

data MArray s S ix e :: Type Source #

Methods

msize :: MArray s S ix e -> Sz ix Source #

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

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

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

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

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

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

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

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

(Index ix, Prim e) => Mutable P ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Primitive

Associated Types

data MArray s P ix e :: Type Source #

Methods

msize :: MArray s P ix e -> Sz ix Source #

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

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

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

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

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

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

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

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

(Index ix, NFData e) => Mutable N ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Associated Types

data MArray s N ix e :: Type Source #

Methods

msize :: MArray s N ix e -> Sz ix Source #

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

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

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

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

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

initialize :: PrimMonad m => MArray (PrimState m) N ix e -> m () Source #

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

unsafeLinearSet :: PrimMonad m => MArray (PrimState m) N ix e -> Int -> Int -> e -> m () Source #

Index ix => Mutable B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

Associated Types

data MArray s B ix e :: Type Source #

Methods

msize :: MArray s B ix e -> Sz ix Source #

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

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

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

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

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

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

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

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

data family MArray s r ix e :: * Source #

Instances
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) !(MVector s 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) !(MutableByteArray s)
data MArray s B ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

data MArray s B ix e = MBArray !(Sz ix) !(MutableArray s e)
newtype MArray s N ix e Source # 
Instance details

Defined in Data.Massiv.Array.Manifest.Boxed

newtype MArray s N ix e = MNArray {}

data RealWorld :: Type #

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#.

computeInto Source #

Arguments

:: (Load r' ix' e, Mutable r ix e, 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, Mutable r ix 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, Mutable r ix 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