Data.Vector.Mutable (original) (raw)

Mutable boxed vectors

data MVector s a Source #

Mutable boxed vectors keyed on the monad they live in (IO or `ST` s).

Instances

Instances details

AccessorsLength informationExtracting subvectors

slice Source #

Yield a part of the mutable vector without copying it. The vector must contain at least i+n elements.

init :: MVector s a -> MVector s a Source #

Drop the last element of the mutable vector without making a copy. If the vector is empty, an exception is thrown.

tail :: MVector s a -> MVector s a Source #

Drop the first element of the mutable vector without making a copy. If the vector is empty, an exception is thrown.

take :: Int -> MVector s a -> MVector s a Source #

Take the n first elements of the mutable vector without making a copy. For negative n, the empty vector is returned. If n is larger than the vector's length, the vector is returned unchanged.

drop :: Int -> MVector s a -> MVector s a Source #

Drop the n first element of the mutable vector without making a copy. For negative n, the vector is returned unchanged. If n is larger than the vector's length, the empty vector is returned.

unsafeSlice Source #

Yield a part of the mutable vector without copying it. No bounds checks are performed.

OverlappingConstructionInitialisation

replicateM :: PrimMonad m => Int -> m a -> m (MVector (PrimState m) a) Source #

Create a mutable vector of the given length (0 if the length is negative) and fill it with values produced by repeatedly executing the monadic action.

generate :: PrimMonad m => Int -> (Int -> a) -> m (MVector (PrimState m) a) Source #

O(n) Create a mutable vector of the given length (0 if the length is negative) and fill it with the results of applying the function to each index. Iteration starts at index 0.

Since: 0.12.3.0

generateM :: PrimMonad m => Int -> (Int -> m a) -> m (MVector (PrimState m) a) Source #

O(n) Create a mutable vector of the given length (0 if the length is negative) and fill it with the results of applying the monadic function to each index. Iteration starts at index 0.

Since: 0.12.3.0

Growing

grow :: PrimMonad m => MVector (PrimState m) a -> Int -> m (MVector (PrimState m) a) Source #

Grow a boxed vector by the given number of elements. The number must be non-negative. This has the same semantics as [grow](Data-Vector-Generic-Mutable.html#v:grow "Data.Vector.Generic.Mutable") for generic vectors. It differs from grow functions for unpacked vectors, however, in that only pointers to values are copied over, therefore the values themselves will be shared between the two vectors. This is an important distinction to know about during memory usage analysis and in case the values themselves are of a mutable type, e.g.[IORef](/package/base-4.18.1.0/docs/Data-IORef.html#v:IORef "Data.IORef") or another mutable vector.

Examples

Expand

>>> import qualified Data.Vector as V** **>>> import qualified Data.Vector.Mutable as MV** **>>> mv <- V.thaw $ V.fromList ([10, 20, 30] :: [Integer])** **>>> mv' <- MV.grow mv 2** **

The two extra elements at the end of the newly allocated vector will be uninitialized and will result in an error if evaluated, so me must overwrite them with new values first:

>>> MV.write mv' 3 999** **>>> MV.write mv' 4 777** **>>> V.freeze mv'** **[10,20,30,999,777]

It is important to note that the source mutable vector is not affected when the newly allocated one is mutated.

>>> MV.write mv' 2 888** **>>> V.freeze mv'** **[10,20,888,999,777] >>> V.freeze mv** **[10,20,30]

Since: 0.5

Restricting memory usageAccessing individual elements

read :: PrimMonad m => MVector (PrimState m) a -> Int -> m a Source #

Yield the element at the given position. Will throw an exception if the index is out of range.

Examples

Expand

>>> import qualified Data.Vector.Mutable as MV** **>>> v <- MV.generate 10 (\x -> x*x)** **>>> **MV.read v 3** ****9

readMaybe :: PrimMonad m => MVector (PrimState m) a -> Int -> m (Maybe a) Source #

Yield the element at the given position. Returns Nothing if the index is out of range.

Examples

Expand

>>> import qualified Data.Vector.Mutable as MV** **>>> v <- MV.generate 10 (\x -> x*x)** **>>> **MV.readMaybe v 3** ****Just 9 >>> **MV.readMaybe v 13** ****Nothing

Since: 0.13

Folds

forM_ :: PrimMonad m => MVector (PrimState m) a -> (a -> m b) -> m () Source #

O(n) Apply the monadic action to every element of the vector, discarding the results. It's the same as flip mapM_.

Since: 0.12.3.0

iforM_ :: PrimMonad m => MVector (PrimState m) a -> (Int -> a -> m b) -> m () Source #

O(n) Apply the monadic action to every element of the vector and its index, discarding the results. It's the same as flip imapM_.

Since: 0.12.3.0

ifoldl' :: PrimMonad m => (b -> Int -> a -> b) -> b -> MVector (PrimState m) a -> m b Source #

O(n) Pure left fold with strict accumulator using a function applied to each element and its index.

Since: 0.12.3.0

ifoldM' :: PrimMonad m => (b -> Int -> a -> m b) -> b -> MVector (PrimState m) a -> m b Source #

O(n) Monadic fold with strict accumulator using a function applied to each element and its index.

Since: 0.12.3.0

ifoldr' :: PrimMonad m => (Int -> a -> b -> b) -> b -> MVector (PrimState m) a -> m b Source #

O(n) Pure right fold with strict accumulator using a function applied to each element and its index.

Since: 0.12.3.0

ifoldrM' :: PrimMonad m => (Int -> a -> b -> m b) -> b -> MVector (PrimState m) a -> m b Source #

O(n) Monadic right fold with strict accumulator using a function applied to each element and its index.

Since: 0.12.3.0

Modifying vectors

nextPermutation :: (PrimMonad m, Ord e) => MVector (PrimState m) e -> m Bool Source #

Compute the (lexicographically) next permutation of the given vector in-place. Returns False when the input is the last item in the enumeration, i.e., if it is in weakly descending order. In this case the vector will not get updated, as opposed to the behavior of the C++ function std::next_permutation.

nextPermutationBy :: PrimMonad m => (e -> e -> Ordering) -> MVector (PrimState m) e -> m Bool Source #

Compute the (lexicographically) next permutation of the given vector in-place, using the provided comparison function. Returns False when the input is the last item in the enumeration, i.e., if it is in weakly descending order. In this case the vector will not get updated, as opposed to the behavior of the C++ function std::next_permutation.

Since: 0.13.2.0

prevPermutation :: (PrimMonad m, Ord e) => MVector (PrimState m) e -> m Bool Source #

Compute the (lexicographically) previous permutation of the given vector in-place. Returns False when the input is the last item in the enumeration, i.e., if it is in weakly ascending order. In this case the vector will not get updated, as opposed to the behavior of the C++ function std::prev_permutation.

Since: 0.13.2.0

prevPermutationBy :: PrimMonad m => (e -> e -> Ordering) -> MVector (PrimState m) e -> m Bool Source #

Compute the (lexicographically) previous permutation of the given vector in-place, using the provided comparison function. Returns False when the input is the last item in the enumeration, i.e., if it is in weakly ascending order. In this case the vector will not get updated, as opposed to the behavior of the C++ function std::prev_permutation.

Since: 0.13.2.0

Filling and copying

copy Source #

Copy a vector. The two vectors must have the same length and may not overlap.

move Source #

Move the contents of a vector. The two vectors must have the same length.

If the vectors do not overlap, then this is equivalent to [copy](Data-Vector-Mutable.html#v:copy "Data.Vector.Mutable"). Otherwise, the copying is performed as if the source vector were copied to a temporary vector and then the temporary vector was copied to the target vector.

unsafeCopy Source #

Copy a vector. The two vectors must have the same length and may not overlap, but this is not checked.

unsafeMove Source #

Move the contents of a vector. The two vectors must have the same length, but this is not checked.

If the vectors do not overlap, then this is equivalent to [unsafeCopy](Data-Vector-Mutable.html#v:unsafeCopy "Data.Vector.Mutable"). Otherwise, the copying is performed as if the source vector were copied to a temporary vector and then the temporary vector was copied to the target vector.

ArraysRe-exports

class Monad m => PrimMonad (m :: Type -> Type) #

Class of monads which can perform primitive state-transformer actions.

Instances

Instances details

PrimMonad IO
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState IO # Methodsprimitive :: (State# (PrimState IO) -> (# State# (PrimState IO), a #)) -> IO a #
PrimMonad (ST s)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (ST s) # Methodsprimitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #
PrimMonad (ST s)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (ST s) # Methodsprimitive :: (State# (PrimState (ST s)) -> (# State# (PrimState (ST s)), a #)) -> ST s a #
PrimMonad m => PrimMonad (MaybeT m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (MaybeT m) # Methodsprimitive :: (State# (PrimState (MaybeT m)) -> (# State# (PrimState (MaybeT m)), a #)) -> MaybeT m a #
(Monoid w, PrimMonad m) => PrimMonad (AccumT w m) Since: primitive-0.6.3.0
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (AccumT w m) # Methodsprimitive :: (State# (PrimState (AccumT w m)) -> (# State# (PrimState (AccumT w m)), a #)) -> AccumT w m a #
PrimMonad m => PrimMonad (ExceptT e m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (ExceptT e m) # Methodsprimitive :: (State# (PrimState (ExceptT e m)) -> (# State# (PrimState (ExceptT e m)), a #)) -> ExceptT e m a #
PrimMonad m => PrimMonad (IdentityT m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (IdentityT m) # Methodsprimitive :: (State# (PrimState (IdentityT m)) -> (# State# (PrimState (IdentityT m)), a #)) -> IdentityT m a #
PrimMonad m => PrimMonad (ReaderT r m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (ReaderT r m) # Methodsprimitive :: (State# (PrimState (ReaderT r m)) -> (# State# (PrimState (ReaderT r m)), a #)) -> ReaderT r m a #
PrimMonad m => PrimMonad (SelectT r m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (SelectT r m) # Methodsprimitive :: (State# (PrimState (SelectT r m)) -> (# State# (PrimState (SelectT r m)), a #)) -> SelectT r m a #
PrimMonad m => PrimMonad (StateT s m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (StateT s m) # Methodsprimitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #
PrimMonad m => PrimMonad (StateT s m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (StateT s m) # Methodsprimitive :: (State# (PrimState (StateT s m)) -> (# State# (PrimState (StateT s m)), a #)) -> StateT s m a #
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (WriterT w m) # Methodsprimitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (WriterT w m) # Methodsprimitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #
(Monoid w, PrimMonad m) => PrimMonad (WriterT w m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (WriterT w m) # Methodsprimitive :: (State# (PrimState (WriterT w m)) -> (# State# (PrimState (WriterT w m)), a #)) -> WriterT w m a #
PrimMonad m => PrimMonad (ContT r m) Since: primitive-0.6.3.0
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (ContT r m) # Methodsprimitive :: (State# (PrimState (ContT r m)) -> (# State# (PrimState (ContT r m)), a #)) -> ContT r m a #
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (RWST r w s m) # Methodsprimitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (RWST r w s m) # Methodsprimitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #
(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m)
Instance detailsDefined in Control.Monad.Primitive Associated Typestype PrimState (RWST r w s m) # Methodsprimitive :: (State# (PrimState (RWST r w s m)) -> (# State# (PrimState (RWST r w s m)), a #)) -> RWST r w s m a #

data RealWorld #

[RealWorld](Data-Vector-Mutable.html#t:RealWorld "Data.Vector.Mutable") is deeply magical. It is primitive, but it is not_unlifted_ (hence ptrArg). We never manipulate values of type[RealWorld](Data-Vector-Mutable.html#t:RealWorld "Data.Vector.Mutable"); it's only used in the type system, to parameterise [State#](/package/base-4.18.1.0/docs/GHC-Exts.html#t:State-35- "GHC.Exts").