grow-vector-0.1.5.0: Mutable vector with efficient appends
Copyright(c) 2020 Gushcha Anton
LicenseMIT
Maintainerncrashed@protonmail.com
Stabilityunstable
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Grow.Storable

Description

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

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.

Constructors

GrowVector 

Fields

Instances

Instances details
Generic (GrowVector s a) Source # 
Instance details

Defined in Data.Vector.Grow.Storable

Associated Types

type Rep (GrowVector s a) :: Type -> Type #

Methods

from :: GrowVector s a -> Rep (GrowVector s a) x #

to :: Rep (GrowVector s a) x -> GrowVector s a #

type Rep (GrowVector s a) Source # 
Instance details

Defined in Data.Vector.Grow.Storable

type Rep (GrowVector s a) = D1 ('MetaData "GrowVector" "Data.Vector.Grow.Storable" "grow-vector-0.1.5.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 :: (Storable a, PrimMonad m) => GrowVector (PrimState m) a -> m Int Source #

Return current amount of elements in the vector

null :: (Storable a, PrimMonad m) => GrowVector (PrimState m) a -> m Bool Source #

Return True if there is no elements inside the vector

capacity :: (Storable 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 :: (Storable a, PrimMonad m) => Int -> m (GrowVector (PrimState m) a) Source #

Allocation of new growable vector with given capacity.

newSized :: (Storable 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

slice Source #

Arguments

:: (Storable 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 :: (Storable 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 :: (Storable 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 :: (Storable a, PrimMonad m) => GrowVector (PrimState m) a -> Int -> m () Source #

Ensure that grow vector has at least given capacity possibly with reallocation.

ensureAppend Source #

Arguments

:: (Storable 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

read Source #

Arguments

:: (Storable 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.

write Source #

Arguments

:: (Storable 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.

unsafeRead Source #

Arguments

:: (Storable 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.

unsafeWrite Source #

Arguments

:: (Storable 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 :: (Storable a, PrimMonad m) => GrowVector (PrimState m) a -> a -> m () Source #

O(1) amortized appending to vector

unsafePushBack :: (Storable 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.