| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Vector.Generic.Mutable.Sized
Contents
Description
This module reexports the functionality in Mutable
which maps well to explicitly sized vectors.
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 resultant vector size is not known until runtime are not exported.
Synopsis
- data MVector v (n :: Nat) s a
- length :: forall v n s a. KnownNat n => MVector v n s a -> Int
- length' :: forall v n s a. MVector v n s a -> Proxy n
- null :: forall v n s a. KnownNat n => MVector v n s a -> Bool
- slice :: forall v i n k s a p. (KnownNat i, KnownNat n, MVector v a) => p i -> MVector v ((i + n) + k) s a -> MVector v n s a
- slice' :: forall v i n k s a p. (KnownNat i, KnownNat n, MVector v a) => p i -> p n -> MVector v ((i + n) + k) s a -> MVector v n s a
- init :: forall v n s a. MVector v a => MVector v (n + 1) s a -> MVector v n s a
- tail :: forall v n s a. MVector v a => MVector v (1 + n) s a -> MVector v n s a
- take :: forall v n k s a. (KnownNat n, MVector v a) => MVector v (n + k) s a -> MVector v n s a
- take' :: forall v n k s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + k) s a -> MVector v n s a
- drop :: forall v n k s a. (KnownNat n, MVector v a) => MVector v (n + k) s a -> MVector v k s a
- drop' :: forall v n k s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + k) s a -> MVector v k s a
- splitAt :: forall v n m s a. (KnownNat n, MVector v a) => MVector v (n + m) s a -> (MVector v n s a, MVector v m s a)
- splitAt' :: forall v n m s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + m) s a -> (MVector v n s a, MVector v m s a)
- overlaps :: forall v n k s a. MVector v a => MVector v n s a -> MVector v k s a -> Bool
- new :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => m (MVector v n (PrimState m) a)
- unsafeNew :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => m (MVector v n (PrimState m) a)
- replicate :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => a -> m (MVector v n (PrimState m) a)
- replicate' :: forall v n m a p. (KnownNat n, PrimMonad m, MVector v a) => p n -> a -> m (MVector v n (PrimState m) a)
- replicateM :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => m a -> m (MVector v n (PrimState m) a)
- replicateM' :: forall v n m a p. (KnownNat n, PrimMonad m, MVector v a) => p n -> m a -> m (MVector v n (PrimState m) a)
- clone :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> m (MVector v n (PrimState m) a)
- grow :: forall v n k m a p. (KnownNat k, PrimMonad m, MVector v a) => p k -> MVector v n (PrimState m) a -> m (MVector v (n + k) (PrimState m) a)
- growFront :: forall v n k m a p. (KnownNat k, PrimMonad m, MVector v a) => p k -> MVector v n (PrimState m) a -> m (MVector v (n + k) (PrimState m) a)
- clear :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> m ()
- read :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> m a
- read' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((n + k) + 1) (PrimState m) a -> p k -> m a
- write :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> a -> m ()
- write' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((n + k) + 1) (PrimState m) a -> p k -> a -> m ()
- modify :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> (a -> a) -> Finite n -> m ()
- modify' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((n + k) + 1) (PrimState m) a -> (a -> a) -> p k -> m ()
- swap :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> Finite n -> m ()
- exchange :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> a -> m a
- exchange' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((n + k) + 1) (PrimState m) a -> p k -> a -> m a
- unsafeRead :: forall v n a m. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> m a
- unsafeWrite :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> a -> m ()
- unsafeModify :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> (a -> a) -> Int -> m ()
- unsafeSwap :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> Int -> m ()
- unsafeExchange :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> a -> m a
- nextPermutation :: forall v n e m. (Ord e, PrimMonad m, MVector v e) => MVector v n (PrimState m) e -> m Bool
- set :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> a -> m ()
- copy :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> MVector v n (PrimState m) a -> m ()
- move :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> MVector v n (PrimState m) a -> m ()
- unsafeCopy :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> MVector v n (PrimState m) a -> m ()
- toSized :: forall v n s a. (MVector v a, KnownNat n) => v s a -> Maybe (MVector v n s a)
- withSized :: forall v s a r. MVector v a => v s a -> (forall n. KnownNat n => MVector v n s a -> r) -> r
- fromSized :: MVector v n s a -> v s a
Documentation
data MVector v (n :: Nat) s a Source #
A wrapper to tag mutable vectors with a type level length.
Be careful when using the constructor here to not construct sized vectors which have a different length than that specified in the type parameter!
Instances
| (KnownNat n, Typeable v, Typeable s, Typeable a, Data (v s a)) => Data (MVector v n s a) Source # | |
| Defined in Data.Vector.Generic.Mutable.Sized.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MVector v n s a -> c (MVector v n s a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (MVector v n s a) # toConstr :: MVector v n s a -> Constr # dataTypeOf :: MVector v n s a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (MVector v n s a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (MVector v n s a)) # gmapT :: (forall b. Data b => b -> b) -> MVector v n s a -> MVector v n s a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MVector v n s a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MVector v n s a -> r # gmapQ :: (forall d. Data d => d -> u) -> MVector v n s a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MVector v n s a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MVector v n s a -> m (MVector v n s a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MVector v n s a -> m (MVector v n s a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MVector v n s a -> m (MVector v n s a) # | |
| Generic (MVector v n s a) Source # | |
| Storable (v s a) => Storable (MVector v n s a) Source # | |
| Defined in Data.Vector.Generic.Mutable.Sized.Internal Methods sizeOf :: MVector v n s a -> Int # alignment :: MVector v n s a -> Int # peekElemOff :: Ptr (MVector v n s a) -> Int -> IO (MVector v n s a) # pokeElemOff :: Ptr (MVector v n s a) -> Int -> MVector v n s a -> IO () # peekByteOff :: Ptr b -> Int -> IO (MVector v n s a) # pokeByteOff :: Ptr b -> Int -> MVector v n s a -> IO () # | |
| NFData (v s a) => NFData (MVector v n s a) Source # | |
| Defined in Data.Vector.Generic.Mutable.Sized.Internal | |
| type Rep (MVector v n s a) Source # | |
| Defined in Data.Vector.Generic.Mutable.Sized.Internal | |
Accessors
Length information
length :: forall v n s a. KnownNat n => MVector v n s a -> Int Source #
O(1) Yield the length of the mutable vector as an Int.
length' :: forall v n s a. MVector v n s a -> Proxy n Source #
O(1) Yield the length of the mutable vector as a Proxy.
null :: forall v n s a. KnownNat n => MVector v n s a -> Bool Source #
O(1) Check whether the mutable vector is empty.
Extracting subvectors
Arguments
| :: (KnownNat i, KnownNat n, MVector v a) | |
| => p i | starting index | 
| -> MVector v ((i + n) + k) s a | |
| -> MVector v n s a | 
O(1) Yield a slice of the mutable vector without copying it with an inferred length argument.
Arguments
| :: (KnownNat i, KnownNat n, MVector v a) | |
| => p i | starting index | 
| -> p n | length | 
| -> MVector v ((i + n) + k) s a | |
| -> MVector v n s a | 
O(1) Yield a slice of the mutable vector without copying it with an explicit length argument.
init :: forall v n s a. MVector v a => MVector v (n + 1) s a -> MVector v n s a Source #
O(1) Yield all but the last element of a non-empty mutable vector without copying.
tail :: forall v n s a. MVector v a => MVector v (1 + n) s a -> MVector v n s a Source #
O(1) Yield all but the first element of a non-empty mutable vector without copying.
take :: forall v n k s a. (KnownNat n, MVector v a) => MVector v (n + k) s a -> MVector v 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 v n k s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + k) s a -> MVector v 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 v n k s a. (KnownNat n, MVector v a) => MVector v (n + k) s a -> MVector v 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 v n k s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + k) s a -> MVector v 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
 given explicitly as a Proxy argument.
splitAt :: forall v n m s a. (KnownNat n, MVector v a) => MVector v (n + m) s a -> (MVector v n s a, MVector v 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 v n m s a p. (KnownNat n, MVector v a) => p n -> MVector v (n + m) s a -> (MVector v n s a, MVector v 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 v n k s a. MVector v a => MVector v n s a -> MVector v k s a -> Bool Source #
O(1) Check whether two vectors overlap.
Construction
Initialisation
new :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => m (MVector v n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type.
unsafeNew :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => m (MVector v n (PrimState m) a) Source #
Create a mutable vector where the length is inferred from the type. The memory is not initialized.
replicate :: forall v n m a. (KnownNat n, PrimMonad m, MVector v a) => a -> m (MVector v 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 v n m a p. (KnownNat n, PrimMonad m, MVector v a) => p n -> a -> m (MVector v 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 v n m a. (KnownNat n, PrimMonad m, MVector v a) => m a -> m (MVector v 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 v n m a p. (KnownNat n, PrimMonad m, MVector v a) => p n -> m a -> m (MVector v 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 v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> m (MVector v n (PrimState m) a) Source #
Create a copy of a mutable vector.
Growing
grow :: forall v n k m a p. (KnownNat k, PrimMonad m, MVector v a) => p k -> MVector v n (PrimState m) a -> m (MVector v (n + k) (PrimState m) a) Source #
Grow a mutable vector by an amount given explicitly as a Proxy
 argument.
growFront :: forall v n k m a p. (KnownNat k, PrimMonad m, MVector v a) => p k -> MVector v n (PrimState m) a -> m (MVector v (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, MVector v a) => MVector v 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 v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> m a Source #
O(1) Yield the element at a given type-safe position using Finite.
read' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((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 v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> a -> m () Source #
O(1) Replace the element at a given type-safe position using Finite.
write' :: forall v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((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 v n m a. (PrimMonad m, MVector v a) => MVector v 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 v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((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 v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Finite n -> Finite n -> m () Source #
O(1) Swap the elements at given type-safe positions using Finites.
exchange :: forall v n m a. (PrimMonad m, MVector v a) => MVector v 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 v n k a m p. (KnownNat k, PrimMonad m, MVector v a) => MVector v ((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 v n a m. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> m a Source #
O(1) Yield the element at a given Int position without bounds
 checking.
unsafeWrite :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> a -> m () Source #
O(1) Replace the element at a given Int position without bounds
 checking.
unsafeModify :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> (a -> a) -> Int -> m () Source #
O(1) Modify the element at a given Int position without bounds
 checking.
unsafeSwap :: forall v n m a. (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> Int -> Int -> m () Source #
O(1) Swap the elements at given Int positions without bounds
 checking.
unsafeExchange :: forall v n m a. (PrimMonad m, MVector v a) => MVector v 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 v n e m. (Ord e, PrimMonad m, MVector v e) => MVector v n (PrimState m) e -> m Bool Source #
Compute the next permutation (in lexicographic order) of a given vector
 in-place.  Returns False when the input is the last permutation.
Filling and copying
set :: (PrimMonad m, MVector v a) => MVector v n (PrimState m) a -> a -> m () Source #
Set all elements of the vector to the given value.
Arguments
| :: (PrimMonad m, MVector v a) | |
| => MVector v n (PrimState m) a | target | 
| -> MVector v n (PrimState m) a | source | 
| -> m () | 
Copy a vector. The two vectors may not overlap.
Arguments
| :: (PrimMonad m, MVector v a) | |
| => MVector v n (PrimState m) a | target | 
| -> MVector v 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.
Arguments
| :: (PrimMonad m, MVector v a) | |
| => MVector v n (PrimState m) a | target | 
| -> MVector v 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 v s a r. MVector v a => v s a -> (forall n. KnownNat n => MVector v 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.