Copyright | (c) 2019 Emily Pillmore |
---|---|
License | BSD-style |
Maintainer | Emily Pillmore <emilypi@cohomolo.gy> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Non-empty mutable boxed vectors.
Synopsis
- data NonEmptyMVector s a
- type NonEmptyIOVector = NonEmptyMVector RealWorld
- type NonEmptySTVector s = NonEmptyMVector s
- length :: NonEmptyMVector s a -> Int
- slice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
- init :: NonEmptyMVector s a -> MVector s a
- tail :: NonEmptyMVector s a -> MVector s a
- take :: Int -> NonEmptyMVector s a -> MVector s a
- drop :: Int -> NonEmptyMVector s a -> MVector s a
- splitAt :: Int -> NonEmptyMVector s a -> (MVector s a, MVector s a)
- unsafeSlice :: Int -> Int -> NonEmptyMVector s a -> MVector s a
- unsafeTake :: Int -> NonEmptyMVector s a -> MVector s a
- unsafeDrop :: Int -> NonEmptyMVector s a -> MVector s a
- overlaps :: NonEmptyMVector s a -> NonEmptyMVector s a -> Bool
- fromMVector :: MVector s a -> Maybe (NonEmptyMVector s a)
- toMVector :: NonEmptyMVector s a -> MVector s a
- unsafeFromMVector :: MVector s a -> NonEmptyMVector s a
- new :: PrimMonad m => Int -> m (Maybe (NonEmptyMVector (PrimState m) a))
- new1 :: PrimMonad m => Int -> m (NonEmptyMVector (PrimState m) a)
- unsafeNew :: PrimMonad m => Int -> m (Maybe (NonEmptyMVector (PrimState m) a))
- replicate :: PrimMonad m => Int -> a -> m (Maybe (NonEmptyMVector (PrimState m) a))
- replicate1 :: PrimMonad m => Int -> a -> m (NonEmptyMVector (PrimState m) a)
- replicateM :: PrimMonad m => Int -> m a -> m (Maybe (NonEmptyMVector (PrimState m) a))
- replicate1M :: PrimMonad m => Int -> m a -> m (Maybe (NonEmptyMVector (PrimState m) a))
- clone :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m (NonEmptyMVector (PrimState m) a)
- grow :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m (NonEmptyMVector (PrimState m) a)
- unsafeGrow :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m (NonEmptyMVector (PrimState m) a)
- clear :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m ()
- read :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m a
- write :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> a -> m ()
- modify :: PrimMonad m => NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m ()
- swap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
- unsafeRead :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m a
- unsafeWrite :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> a -> m ()
- unsafeModify :: PrimMonad m => NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m ()
- unsafeSwap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m ()
- nextPermutation :: (PrimMonad m, Ord e) => NonEmptyMVector (PrimState m) e -> m Bool
- set :: PrimMonad m => NonEmptyMVector (PrimState m) a -> a -> m ()
- copy :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m ()
- move :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m ()
- unsafeCopy :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m ()
- unsafeMove :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m ()
Mutable boxed vectors
data NonEmptyMVector s a Source #
NonEmptyMVector
is a thin wrapper around MVector
that
witnesses an API requiring non-empty construction,
initialization, and generation of non-empty vectors by design.
A newtype wrapper was chosen so that no new pointer indirection
is introduced when working with MVector
s, and all performance
characteristics inherited from the MVector
API still apply.
type NonEmptyIOVector = NonEmptyMVector RealWorld Source #
NonEmptyMVector
parametrized by PrimState
type NonEmptySTVector s = NonEmptyMVector s Source #
NonEmptyMVector
parametrized by ST
Accessors
Length information
length :: NonEmptyMVector s a -> Int Source #
Length of the mutable vector.
Extracting subvectors
slice :: Int -> Int -> NonEmptyMVector s a -> MVector s a Source #
Yield a part of the mutable vector without copying.
init :: NonEmptyMVector s a -> MVector s a Source #
Yield all but the last element without copying.
tail :: NonEmptyMVector s a -> MVector s a Source #
Yield all but the first element without copying.
take :: Int -> NonEmptyMVector s a -> MVector s a Source #
Yield at the first n elements without copying.
drop :: Int -> NonEmptyMVector s a -> MVector s a Source #
Yield all but the first n elements without copying.
splitAt :: Int -> NonEmptyMVector s a -> (MVector s a, MVector s a) Source #
Yield the first n elements paired with the remainder without copying.
:: Int | starting index |
-> Int | length of the slice |
-> NonEmptyMVector s a | |
-> MVector s a |
Yield a part of the mutable vector without copying it. No bounds checks are performed.
unsafeTake :: Int -> NonEmptyMVector s a -> MVector s a Source #
Yield the first n elements without copying. The vector must contain at least n elements but this is not checked.
unsafeDrop :: Int -> NonEmptyMVector s a -> MVector s a Source #
Yield all but the first n elements without copying. The vector must contain at least n elements but this is not checked.
Overlapping
overlaps :: NonEmptyMVector s a -> NonEmptyMVector s a -> Bool Source #
Check whether two vectors overlap.
Conversions
fromMVector :: MVector s a -> Maybe (NonEmptyMVector s a) Source #
Convert a mutable vector to a non-empty mutable vector
toMVector :: NonEmptyMVector s a -> MVector s a Source #
Convert a non-empty mutable vector to a mutable vector
unsafeFromMVector :: MVector s a -> NonEmptyMVector s a Source #
Convert a mutable vector to a non-empty mutable vector
Warning: this function is unsafe and can result in empty non-empty mutable vectors. If you call this function, the onus is on you to make sure the mutable vector being converted is not empty.
Initialisation
new :: PrimMonad m => Int -> m (Maybe (NonEmptyMVector (PrimState m) a)) Source #
Create a mutable vector of the given length.
new1 :: PrimMonad m => Int -> m (NonEmptyMVector (PrimState m) a) Source #
Create a mutable vector of the given length which is
max n 1
.
unsafeNew :: PrimMonad m => Int -> m (Maybe (NonEmptyMVector (PrimState m) a)) Source #
Create a mutable vector of the given length. The memory is not initialized.
replicate :: PrimMonad m => Int -> a -> m (Maybe (NonEmptyMVector (PrimState m) a)) Source #
Create a mutable vector of the given length (0 if the length is negative) and fill it with an initial value.
replicate1 :: PrimMonad m => Int -> a -> m (NonEmptyMVector (PrimState m) a) Source #
Create a mutable vector of the length max n 1
for a given length,
and fill it with an initial value.
replicateM :: PrimMonad m => Int -> m a -> m (Maybe (NonEmptyMVector (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.
replicate1M :: PrimMonad m => Int -> m a -> m (Maybe (NonEmptyMVector (PrimState m) a)) Source #
Create a mutable vector of the length max n 1
for a given length,
and fill it with values produced by repeatedly executing the monadic action.
clone :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m (NonEmptyMVector (PrimState m) a) Source #
Create a copy of a mutable vector.
Growing
grow :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m (NonEmptyMVector (PrimState m) a) Source #
Grow a vector by the given number of elements. The number must be positive.
unsafeGrow :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m (NonEmptyMVector (PrimState m) a) Source #
Grow a vector by the given number of elements. The number must be positive but this is not checked.
Restricting memory usage
clear :: PrimMonad m => NonEmptyMVector (PrimState m) a -> m () Source #
Reset all elements of the vector to some undefined value, clearing all references to external objects. This is usually a noop for unboxed vectors.
Accessing individual elements
read :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m a Source #
Yield the element at the given position.
write :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> a -> m () Source #
Replace the element at the given position.
modify :: PrimMonad m => NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m () Source #
Modify the element at the given position.
swap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m () Source #
Swap the elements at the given positions.
unsafeRead :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> m a Source #
Yield the element at the given position. No bounds checks are performed.
unsafeWrite :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> a -> m () Source #
Replace the element at the given position. No bounds checks are performed.
unsafeModify :: PrimMonad m => NonEmptyMVector (PrimState m) a -> (a -> a) -> Int -> m () Source #
Modify the element at the given position. No bounds checks are performed.
unsafeSwap :: PrimMonad m => NonEmptyMVector (PrimState m) a -> Int -> Int -> m () Source #
Swap the elements at the given positions. No bounds checks are performed.
Modifying vectors
nextPermutation :: (PrimMonad m, Ord e) => NonEmptyMVector (PrimState m) e -> m Bool Source #
Compute the next (lexicographically) permutation of given vector in-place. Returns False when input is the last permtuation
Filling and copying
set :: PrimMonad m => NonEmptyMVector (PrimState m) a -> a -> m () Source #
Set all elements of the vector to the given value.
copy :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m () Source #
Copy a vector. The two vectors must have the same length and may not overlap.
move :: PrimMonad m => NonEmptyMVector (PrimState m) a -> NonEmptyMVector (PrimState m) a -> m () 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
.
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.
:: PrimMonad m | |
=> NonEmptyMVector (PrimState m) a | target |
-> NonEmptyMVector (PrimState m) a | source |
-> m () |
Copy a vector. The two vectors must have the same length and may not overlap. This is not checked.
:: PrimMonad m | |
=> NonEmptyMVector (PrimState m) a | target |
-> NonEmptyMVector (PrimState m) a | source |
-> m () |
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
.
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.