Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module re-exports the functionality in Sized
specialized to Mutable
.
Functions returning a vector determine the size from the type context unless
they have a '
suffix in which case they take an explicit Proxy
argument.
Functions where the resulting vector size is not known until runtime are not exported.
Synopsis
- type MVector = MVector MVector
- length :: forall n s a. KnownNat n => MVector n s a -> Int
- length' :: forall n s a. MVector n s a -> Proxy n
- null :: forall n s a. KnownNat n => MVector n s a -> Bool
- slice :: forall i n k s a p. (KnownNat i, KnownNat n, Storable a) => p i -> MVector ((i + n) + k) s a -> MVector n s a
- slice' :: forall i n k s a p. (KnownNat i, KnownNat n, Storable a) => p i -> p n -> MVector ((i + n) + k) s a -> MVector n s a
- init :: forall n s a. Storable a => MVector (n + 1) s a -> MVector n s a
- tail :: forall n s a. Storable a => MVector (1 + n) s a -> MVector n s a
- take :: forall n k s a. (KnownNat n, Storable a) => MVector (n + k) s a -> MVector n s a
- take' :: forall n k s a p. (KnownNat n, Storable a) => p n -> MVector (n + k) s a -> MVector n s a
- drop :: forall n k s a. (KnownNat n, Storable a) => MVector (n + k) s a -> MVector k s a
- drop' :: forall n k s a p. (KnownNat n, Storable a) => p n -> MVector (n + k) s a -> MVector k s a
- splitAt :: forall n m s a. (KnownNat n, Storable a) => MVector (n + m) s a -> (MVector n s a, MVector m s a)
- splitAt' :: forall n m s a p. (KnownNat n, Storable a) => p n -> MVector (n + m) s a -> (MVector n s a, MVector m s a)
- overlaps :: forall n k s a. Storable a => MVector n s a -> MVector k s a -> Bool
- new :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m (MVector n (PrimState m) a)
- unsafeNew :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m (MVector n (PrimState m) a)
- replicate :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => a -> m (MVector n (PrimState m) a)
- replicate' :: forall n m a p. (KnownNat n, PrimMonad m, Storable a) => p n -> a -> m (MVector n (PrimState m) a)
- replicateM :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m a -> m (MVector n (PrimState m) a)
- replicateM' :: forall n m a p. (KnownNat n, PrimMonad m, Storable a) => p n -> m a -> m (MVector n (PrimState m) a)
- clone :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> m (MVector n (PrimState m) a)
- grow :: forall n k m a p. (KnownNat k, PrimMonad m, Storable a) => p k -> MVector n (PrimState m) a -> m (MVector (n + k) (PrimState m) a)
- growFront :: forall n k m a p. (KnownNat k, PrimMonad m, Storable a) => p k -> MVector n (PrimState m) a -> m (MVector (n + k) (PrimState m) a)
- clear :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> m ()
- read :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> m a
- read' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> m a
- write :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> a -> m ()
- write' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> a -> m ()
- modify :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> (a -> a) -> Finite n -> m ()
- modify' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> (a -> a) -> p k -> m ()
- swap :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> Finite n -> m ()
- exchange :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> a -> m a
- exchange' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> a -> m a
- unsafeRead :: forall n a m. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> m a
- unsafeWrite :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> a -> m ()
- unsafeModify :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> (a -> a) -> Int -> m ()
- unsafeSwap :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> Int -> m ()
- unsafeExchange :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> a -> m a
- nextPermutation :: forall n e m. (Ord e, PrimMonad m, Storable e) => MVector n (PrimState m) e -> m Bool
- set :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> a -> m ()
- copy :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> MVector n (PrimState m) a -> m ()
- move :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> MVector n (PrimState m) a -> m ()
- unsafeCopy :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> MVector n (PrimState m) a -> m ()
- toSized :: forall n a s. (KnownNat n, Storable a) => MVector s a -> Maybe (MVector n s a)
- withSized :: forall s a r. Storable a => MVector s a -> (forall n. KnownNat n => MVector n s a -> r) -> r
- fromSized :: MVector n s a -> MVector s a
Documentation
Accessors
Length information
length :: forall n s a. KnownNat n => MVector n s a -> Int Source #
O(1) Yield the length of the mutable vector as an Int
.
length' :: forall n s a. MVector n s a -> Proxy n Source #
O(1) Yield the length of the mutable vector as a Proxy
.
null :: forall n s a. KnownNat n => MVector n s a -> Bool Source #
O(1) Check whether the mutable vector is empty.
Extracting subvectors
:: forall i n k s a p. (KnownNat i, KnownNat n, Storable a) | |
=> p i | starting index |
-> MVector ((i + n) + k) s a | |
-> MVector n s a |
O(1) Yield a slice of the mutable vector without copying it with an inferred length argument.
:: forall i n k s a p. (KnownNat i, KnownNat n, Storable a) | |
=> p i | starting index |
-> p n | length |
-> MVector ((i + n) + k) s a | |
-> MVector n s a |
O(1) Yield a slice of the mutable vector without copying it with an explicit length argument.
init :: forall n s a. Storable a => MVector (n + 1) s a -> MVector n s a Source #
O(1) Yield all but the last element of a non-empty mutable vector without copying.
tail :: forall n s a. Storable a => MVector (1 + n) s a -> MVector n s a Source #
O(1) Yield all but the first element of a non-empty mutable vector without copying.
take :: forall n k s a. (KnownNat n, Storable a) => MVector (n + k) s a -> MVector n s a Source #
O(1) Yield the first n
elements. The resulting vector always contains
this many elements. The length of the resulting vector is inferred from the
type.
take' :: forall n k s a p. (KnownNat n, Storable a) => p n -> MVector (n + k) s a -> MVector n s a Source #
O(1) Yield the first n
elements. The resulting vector always contains
this many elements. The length of the resulting vector is given explicitly
as a Proxy
argument.
drop :: forall n k s a. (KnownNat n, Storable a) => MVector (n + k) s a -> MVector k s a Source #
O(1) Yield all but the the first n
elements. The given vector must
contain at least this many elements. The length of the resulting vector is
inferred from the type.
drop' :: forall n k s a p. (KnownNat n, Storable a) => p n -> MVector (n + k) s a -> MVector k s a Source #
O(1) Yield all but the the first n
elements. The given vector must
contain at least this many elements. The length of the resulting vector is
givel explicitly as a Proxy
argument.
splitAt :: forall n m s a. (KnownNat n, Storable a) => MVector (n + m) s a -> (MVector n s a, MVector m s a) Source #
O(1) Yield the first n
elements, paired with the rest, without copying.
The lengths of the resulting vectors are inferred from the type.
splitAt' :: forall n m s a p. (KnownNat n, Storable a) => p n -> MVector (n + m) s a -> (MVector n s a, MVector m s a) Source #
O(1) Yield the first n
elements, paired with the rest, without
copying. The length of the first resulting vector is passed explicitly as a
Proxy
argument.
Overlaps
overlaps :: forall n k s a. Storable a => MVector n s a -> MVector k s a -> Bool Source #
O(1) Check if two vectors overlap.
Construction
Initialisation
new :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type.
unsafeNew :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type. The memory is not initialized.
replicate :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => a -> m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type and fill it with an initial value.
replicate' :: forall n m a p. (KnownNat n, PrimMonad m, Storable a) => p n -> a -> m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is given explicitly as
a Proxy
argument and fill it with an initial value.
replicateM :: forall n m a. (KnownNat n, PrimMonad m, Storable a) => m a -> m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type and fill it with values produced by repeatedly executing the monadic action.
replicateM' :: forall n m a p. (KnownNat n, PrimMonad m, Storable a) => p n -> m a -> m (MVector n (PrimState m) a) Source #
Create a mutable vector where the length is given explicitly as
a Proxy
argument and fill it with values produced by repeatedly
executing the monadic action.
clone :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> m (MVector n (PrimState m) a) Source #
Create a copy of a mutable vector.
Growing
grow :: forall n k m a p. (KnownNat k, PrimMonad m, Storable a) => p k -> MVector n (PrimState m) a -> m (MVector (n + k) (PrimState m) a) Source #
Grow a mutable vector by an amount given explicitly as a Proxy
argument.
growFront :: forall n k m a p. (KnownNat k, PrimMonad m, Storable a) => p k -> MVector n (PrimState m) a -> m (MVector (n + k) (PrimState m) a) Source #
Grow a mutable vector (from the front) by an amount given explicitly
as a Proxy
argument.
Restricting memory usage
clear :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> m () Source #
Reset all elements of the vector to some undefined value, clearing all references to external objects.
Accessing individual elements
read :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> m a Source #
O(1) Yield the element at a given type-safe position using Finite
.
read' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> m a Source #
O(1) Yield the element at a given type-safe position using Proxy
.
write :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> a -> m () Source #
O(1) Replace the element at a given type-safe position using Finite
.
write' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> a -> m () Source #
O(1) Replace the element at a given type-safe position using Proxy
.
modify :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> (a -> a) -> Finite n -> m () Source #
O(1) Modify the element at a given type-safe position using Finite
.
modify' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> (a -> a) -> p k -> m () Source #
O(1) Modify the element at a given type-safe position using Proxy
.
swap :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> Finite n -> m () Source #
O(1) Swap the elements at the given type-safe positions using Finite
s.
exchange :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Finite n -> a -> m a Source #
O(1) Replace the element at a given type-safe position and return
the old element, using Finite
.
exchange' :: forall n k a m p. (KnownNat k, PrimMonad m, Storable a) => MVector ((n + k) + 1) (PrimState m) a -> p k -> a -> m a Source #
O(1) Replace the element at a given type-safe position and return
the old element, using Finite
.
unsafeRead :: forall n a m. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> m a Source #
O(1) Yield the element at a given Int
position without bounds
checking.
unsafeWrite :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> a -> m () Source #
O(1) Replace the element at a given Int
position without bounds
checking.
unsafeModify :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> (a -> a) -> Int -> m () Source #
O(1) Modify the element at a given Int
position without bounds
checking.
unsafeSwap :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> Int -> m () Source #
O(1) Swap the elements at the given Int
positions without bounds
checking.
unsafeExchange :: forall n m a. (PrimMonad m, Storable a) => MVector n (PrimState m) a -> Int -> a -> m a Source #
O(1) Replace the element at a given Int
position and return
the old element. No bounds checks are performed.
Modifying vectors
nextPermutation :: forall n e m. (Ord e, PrimMonad m, Storable e) => MVector n (PrimState m) e -> m Bool Source #
Compute the next permutation (lexicographically) of a given vector
in-place. Returns False
when the input is the last permutation.
Filling and copying
set :: (PrimMonad m, Storable a) => MVector n (PrimState m) a -> a -> m () Source #
Set all elements of the vector to the given value.
:: (PrimMonad m, Storable a) | |
=> MVector n (PrimState m) a | target |
-> MVector n (PrimState m) a | source |
-> m () |
Copy a vector. The two vectors may not overlap.
:: (PrimMonad m, Storable a) | |
=> MVector n (PrimState m) a | target |
-> MVector n (PrimState m) a | source |
-> m () |
Move the contents of a vector. If the two vectors do not overlap,
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, Storable a) | |
=> MVector n (PrimState m) a | target |
-> MVector n (PrimState m) a | source |
-> m () |
Copy a vector. The two vectors may not overlap. This is not checked.
Conversions
Unsized Mutable Vectors
withSized :: forall s a r. Storable a => MVector s a -> (forall n. KnownNat n => MVector n s a -> r) -> r Source #
Takes a MVector
and returns
a continuation providing a MVector
with a size parameter n
that is determined at runtime based on the
length of the input vector.
Essentially converts a MVector
into
a MVector
with the correct size parameter
n
.
Note that this does no copying; the returned MVector
is a reference to
the exact same vector in memory as the given one, and any modifications
to it are also reflected in the given
MVector
.