Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Mutable vectors with a linear API.
Vectors are arrays that grow automatically, that you can append to with
push
. They never shrink automatically to reduce unnecessary copying,
use shrinkToFit
to get rid of the wasted space.
To use mutable vectors, create a linear computation of type
Vector a %1-> Ur b
and feed it to constant
or fromList
.
Example
>>>
:set -XLinearTypes
>>>
import Prelude.Linear
>>>
import qualified Data.Vector.Mutable.Linear as Vector
>>>
:{
isFirstZero :: Vector.Vector Int %1-> Ur Bool isFirstZero vec = Vector.get 0 vec & \(Ur ret, vec) -> vec `lseq` Ur (ret == 0) :}
>>>
unur $ Vector.fromList [0..10] isFirstZero
True>>>
unur $ Vector.fromList [1,2,3] isFirstZero
False
Synopsis
- data Vector a
- empty :: (Vector a %1 -> Ur b) %1 -> Ur b
- constant :: HasCallStack => Int -> a -> (Vector a %1 -> Ur b) %1 -> Ur b
- fromList :: HasCallStack => [a] -> (Vector a %1 -> Ur b) %1 -> Ur b
- set :: HasCallStack => Int -> a -> Vector a %1 -> Vector a
- unsafeSet :: HasCallStack => Int -> a -> Vector a %1 -> Vector a
- modify :: HasCallStack => (a -> (a, b)) -> Int -> Vector a %1 -> (Ur b, Vector a)
- modify_ :: HasCallStack => (a -> a) -> Int -> Vector a %1 -> Vector a
- push :: a -> Vector a %1 -> Vector a
- pop :: Vector a %1 -> (Ur (Maybe a), Vector a)
- filter :: Vector a %1 -> (a -> Bool) -> Vector a
- mapMaybe :: Vector a %1 -> (a -> Maybe b) -> Vector b
- slice :: Int -> Int -> Vector a %1 -> Vector a
- shrinkToFit :: Vector a %1 -> Vector a
- get :: HasCallStack => Int -> Vector a %1 -> (Ur a, Vector a)
- unsafeGet :: HasCallStack => Int -> Vector a %1 -> (Ur a, Vector a)
- size :: Vector a %1 -> (Ur Int, Vector a)
- capacity :: Vector a %1 -> (Ur Int, Vector a)
- toList :: Vector a %1 -> Ur [a]
- freeze :: Vector a %1 -> Ur (Vector a)
- read :: HasCallStack => Vector a %1 -> Int -> (Ur a, Vector a)
- unsafeRead :: Vector a %1 -> Int -> (Ur a, Vector a)
- write :: HasCallStack => Vector a %1 -> Int -> a -> Vector a
- unsafeWrite :: Vector a %1 -> Int -> a -> Vector a
A mutable vector
A dynamic mutable vector.
Run a computation with a vector
constant :: HasCallStack => Int -> a -> (Vector a %1 -> Ur b) %1 -> Ur b Source #
Allocate a constant vector of a given non-negative size (and error on a bad size)
Mutators
set :: HasCallStack => Int -> a -> Vector a %1 -> Vector a Source #
Write to an element . Note: this will not write to elements beyond the current size of the vector and will error instead.
unsafeSet :: HasCallStack => Int -> a -> Vector a %1 -> Vector a Source #
Same as write
, but does not do bounds-checking. The behaviour is undefined
when passed an invalid index.
modify :: HasCallStack => (a -> (a, b)) -> Int -> Vector a %1 -> (Ur b, Vector a) Source #
Modify a value inside a vector, with an ability to return an extra information. Errors if the index is out of bounds.
modify_ :: HasCallStack => (a -> a) -> Int -> Vector a %1 -> Vector a Source #
Same as modify
, but without the ability to return extra information.
push :: a -> Vector a %1 -> Vector a Source #
Insert at the end of the vector. This will grow the vector if there is no empty space.
pop :: Vector a %1 -> (Ur (Maybe a), Vector a) Source #
Pop from the end of the vector. This will never shrink the vector, use
shrinkToFit
to remove the wasted space.
filter :: Vector a %1 -> (a -> Bool) -> Vector a Source #
Filters the vector in-place. It does not deallocate unused capacity,
use shrinkToFit
for that if necessary.
mapMaybe :: Vector a %1 -> (a -> Maybe b) -> Vector b Source #
A version of fmap
which can throw out elements.
slice :: Int -> Int -> Vector a %1 -> Vector a Source #
Return a slice of the vector with given size, starting from an offset.
Start offset + target size should be within the input vector, and both should be non-negative.
This is a constant time operation if the start offset is 0. Use shrinkToFit
to remove the possible wasted space if necessary.
shrinkToFit :: Vector a %1 -> Vector a Source #
Resize the vector to not have any wasted memory (size == capacity). This returns a semantically identical vector.
Accessors
get :: HasCallStack => Int -> Vector a %1 -> (Ur a, Vector a) Source #
Read from a vector, with an in-range index and error for an index that is
out of range (with the usual range 0..size-1
).
unsafeGet :: HasCallStack => Int -> Vector a %1 -> (Ur a, Vector a) Source #
Same as read
, but does not do bounds-checking. The behaviour is undefined
when passed an invalid index.
size :: Vector a %1 -> (Ur Int, Vector a) Source #
Number of elements inside the vector.
This might be different than how much actual memory the vector is using.
For that, see: capacity
.
capacity :: Vector a %1 -> (Ur Int, Vector a) Source #
Capacity of a vector. In other words, the number of elements the vector can contain before it is copied to a bigger array.