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

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

Data.Massiv.Array.Mutable

Contents

Description

 
Synopsis

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. Return Nothing when index is out of bounds.

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

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

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, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> e -> m () Source #

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

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, 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, PrimMonad m) => MArray (PrimState m) r ix e -> ix -> ix -> m () Source #

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

Operate over Array

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 #

unsafeNewZero :: 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 #

unsafeNewA :: Applicative f => ix -> WorldState -> f (WorldState, MArray RealWorld U ix e)

unsafeThawA :: Applicative m => Array U ix e -> WorldState -> m (WorldState, MArray RealWorld U ix e)

unsafeFreezeA :: Applicative m => Comp -> MArray RealWorld U ix e -> WorldState -> m (WorldState, Array U ix e)

unsafeLinearWriteA :: Applicative m => MArray RealWorld U ix e -> Int -> e -> WorldState -> m WorldState

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

unsafeNewZero :: 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 #

unsafeNewA :: Applicative f => ix -> WorldState -> f (WorldState, MArray RealWorld S ix e)

unsafeThawA :: Applicative m => Array S ix e -> WorldState -> m (WorldState, MArray RealWorld S ix e)

unsafeFreezeA :: Applicative m => Comp -> MArray RealWorld S ix e -> WorldState -> m (WorldState, Array S ix e)

unsafeLinearWriteA :: Applicative m => MArray RealWorld S ix e -> Int -> e -> WorldState -> m WorldState

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

unsafeNewZero :: 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 #

unsafeNewA :: Applicative f => ix -> WorldState -> f (WorldState, MArray RealWorld P ix e)

unsafeThawA :: Applicative m => Array P ix e -> WorldState -> m (WorldState, MArray RealWorld P ix e)

unsafeFreezeA :: Applicative m => Comp -> MArray RealWorld P ix e -> WorldState -> m (WorldState, Array P ix e)

unsafeLinearWriteA :: Applicative m => MArray RealWorld P ix e -> Int -> e -> WorldState -> m WorldState

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

unsafeNewZero :: 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 #

unsafeNewA :: Applicative f => ix -> WorldState -> f (WorldState, MArray RealWorld N ix e)

unsafeThawA :: Applicative m => Array N ix e -> WorldState -> m (WorldState, MArray RealWorld N ix e)

unsafeFreezeA :: Applicative m => Comp -> MArray RealWorld N ix e -> WorldState -> m (WorldState, Array N ix e)

unsafeLinearWriteA :: Applicative m => MArray RealWorld N ix e -> Int -> e -> WorldState -> m WorldState

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 #

unsafeNewZero :: 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 #

unsafeNewA :: Applicative f => ix -> WorldState -> f (WorldState, MArray RealWorld B ix e)

unsafeThawA :: Applicative m => Array B ix e -> WorldState -> m (WorldState, MArray RealWorld B ix e)

unsafeFreezeA :: Applicative m => Comp -> MArray RealWorld B ix e -> WorldState -> m (WorldState, Array B ix e)

unsafeLinearWriteA :: Applicative m => MArray RealWorld B ix e -> Int -> e -> WorldState -> m WorldState

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 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 !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 !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 !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 {}

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

Get the size of a mutable array.

Convert

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

Initialize a new mutable array. Negative size will result in an empty array.

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

O(n) - Yield a mutable copy of the immutable array

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

O(n) - Yield an immutable copy of the mutable array

Create

createArray_ Source #

Arguments

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

Computation strategy to use after Array 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 createArray if you'd like to keep the result of the filling function.

Examples

Expand
>>> createArray_ Seq (Sz1 2) (\ marr -> write marr 0 10 >> write marr 1 11) :: IO (Array P Ix1 Int)
(Array P Seq (2)
  [ 10,11 ])

Since: 0.2.6

createArray Source #

Arguments

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

Computation strategy to use after Array 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.2.6

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

Just like createArray_, but restricted to ST.

Since: 0.2.6

createArrayST :: 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 createArray, but restricted to ST.

Since: 0.2.6

Generate

generateArray 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.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 (6)
  [ 0,1,2,3,4,5 ])
>>> readIORef ref
15

Since: 0.2.6

generateArrayIO :: Mutable r ix e => Comp -> Sz ix -> (ix -> IO e) -> IO (Array r ix e) Source #

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

Since: 0.2.6

Unfold

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

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.

>>> unfoldlPrim_ Seq  (Ix1 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 (10)
  [ 0,1,1,2,3,5,8,13,21,34 ])

Since: 0.2.6

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

Since: 0.2.6

Modify

withMArray :: (Mutable r ix e, PrimMonad m) => Array r ix e -> (MArray (PrimState m) 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.

Since: 0.2.2

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 withMArray but in ST.

Since: 0.2.2

Computation

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) 
=> MArray RealWorld r ix e

Target Array

-> Array r' ix e

Array to load

-> IO () 

Compute an Array while loading the results into the supplied mutable target array. Sizes of both arrays must agree, otherwise error.

Since: 0.1.3