Copyright | (c) 2020 Gushcha Anton |
---|---|
License | MIT |
Maintainer | ncrashed@protonmail.com |
Stability | unstable |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Module defines mutable vector that can grow in size automatically when an user adds new elements at the end of vector.
We reallocate vector with 1.5x length to get amortized append.
Synopsis
- data GrowVector s a = GrowVector {
- growVector :: !(MutVar s (MVector s a))
- growVectorLength :: !(MutVar s Int)
- type IOGrowVector a = GrowVector RealWorld a
- length :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Int
- null :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Bool
- capacity :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Int
- new :: (Unbox a, PrimMonad m) => Int -> m (GrowVector (PrimState m) a)
- newSized :: (Unbox a, PrimMonad m) => Int -> Int -> m (GrowVector (PrimState m) a)
- slice :: (Unbox a, PrimMonad m) => Int -> Int -> GrowVector (PrimState m) a -> m (GrowVector (PrimState m) a)
- thaw :: (Unbox a, PrimMonad m) => Vector a -> m (GrowVector (PrimState m) a)
- freeze :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m (Vector a)
- ensure :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m ()
- ensureAppend :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m ()
- read :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m a
- write :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> a -> m ()
- unsafeRead :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m a
- unsafeWrite :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> a -> m ()
- pushBack :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> a -> m ()
- unsafePushBack :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> a -> m ()
Documentation
data GrowVector s a Source #
Grow vector that is wrap around mutable vector. We allocate partially filled vector and grow it when there is no more space for new element.
GrowVector | |
|
Instances
Generic (GrowVector s a) Source # | |
Defined in Data.Vector.Grow.Unboxed type Rep (GrowVector s a) :: Type -> Type # from :: GrowVector s a -> Rep (GrowVector s a) x # to :: Rep (GrowVector s a) x -> GrowVector s a # | |
type Rep (GrowVector s a) Source # | |
Defined in Data.Vector.Grow.Unboxed type Rep (GrowVector s a) = D1 ('MetaData "GrowVector" "Data.Vector.Grow.Unboxed" "grow-vector-0.1.1.0-inplace" 'False) (C1 ('MetaCons "GrowVector" 'PrefixI 'True) (S1 ('MetaSel ('Just "growVector") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MutVar s (MVector s a))) :*: S1 ('MetaSel ('Just "growVectorLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MutVar s Int)))) |
type IOGrowVector a = GrowVector RealWorld a Source #
Synonim for GrowVector
in IO
monad
Quering info about vector
length :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Int Source #
Return current amount of elements in the vector
null :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Bool Source #
Return True
if there is no elements inside the vector
capacity :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m Int Source #
Return current capacity of the vector (amount of elements that it can fit without realloc)
Creation
new :: (Unbox a, PrimMonad m) => Int -> m (GrowVector (PrimState m) a) Source #
Allocation of new growable vector with given capacity.
newSized :: (Unbox a, PrimMonad m) => Int -> Int -> m (GrowVector (PrimState m) a) Source #
Allocation of new growable vector with given filled size and capacity. Elements is not initialized. Capacity must be greater than filled size.
Quering subvectors
:: (Unbox a, PrimMonad m) | |
=> Int | i starting index |
-> Int | n number of elements |
-> GrowVector (PrimState m) a | |
-> m (GrowVector (PrimState m) a) |
Yield a part of mutable vector without copying it. The vector must contain at least i+n elements.
Converting to immutable
thaw :: (Unbox a, PrimMonad m) => Vector a -> m (GrowVector (PrimState m) a) Source #
Convert immutable vector to grow mutable version. Doesn't allocate additonal memory for appending,
use ensure
to add capacity to the vector.
freeze :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> m (Vector a) Source #
Freezing growable vector. It will contain only actual elements of the vector not including capacity
space, but you should call force
on resulting vector to not hold the allocated capacity of original
vector in memory.
Capacity maninuplation
ensure :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m () Source #
Ensure that grow vector has at least given capacity possibly with reallocation.
:: (Unbox a, PrimMonad m) | |
=> GrowVector (PrimState m) a | |
-> Int | Additional n elements |
-> m () |
Ensure that grow vector has enough space for additonal n elements. We grow vector by 1.5 factor or by required elements count * 1.5.
Accessing individual elements
:: (Unbox a, PrimMonad m) | |
=> GrowVector (PrimState m) a | |
-> Int | Index of element. Must be in [0 .. length) range |
-> m a |
Read element from vector at given index.
:: (Unbox a, PrimMonad m) | |
=> GrowVector (PrimState m) a | |
-> Int | Index of element. Must be in [0 .. length) range |
-> a | |
-> m () |
Write down element in the vector at given index.
:: (Unbox a, PrimMonad m) | |
=> GrowVector (PrimState m) a | |
-> Int | Index of element. Must be in [0 .. length) range |
-> m a |
Read element from vector at given index.
:: (Unbox a, PrimMonad m) | |
=> GrowVector (PrimState m) a | |
-> Int | Index of element. Must be in [0 .. length) range |
-> a | |
-> m () |
Write down element in the vector at given index.
Appending to vector
pushBack :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> a -> m () Source #
O(1) amortized appending to vector
unsafePushBack :: (Unbox a, PrimMonad m) => GrowVector (PrimState m) a -> a -> m () Source #
O(1) amortized appending to vector. Doesn't reallocate vector, so there must by capacity - length >= 1.