Safe Haskell | None |
---|---|
Language | Haskell2010 |
This is a port of the persistent vector from clojure to Haskell. It is spine-strict and lazy in the elements.
The implementation is based on array mapped tries. The complexity bounds given are mostly O(1), but only if you are willing to accept that the tree cannot have height greater than 7 on 32 bit systems and maybe 8 on 64 bit systems.
Synopsis
- data Vector a
- empty :: Vector a
- singleton :: a -> Vector a
- snoc :: Vector a -> a -> Vector a
- fromList :: [a] -> Vector a
- append :: Vector a -> Vector a -> Vector a
- null :: Vector a -> Bool
- length :: Vector a -> Int
- index :: Vector a -> Int -> Maybe a
- unsafeIndex :: Vector a -> Int -> a
- unsafeIndexA :: Applicative f => Vector a -> Int -> f a
- unsafeIndex# :: Vector a -> Int -> (# a #)
- take :: Int -> Vector a -> Vector a
- drop :: Int -> Vector a -> Vector a
- splitAt :: Int -> Vector a -> (Vector a, Vector a)
- slice :: Int -> Int -> Vector a -> Vector a
- shrink :: Vector a -> Vector a
- update :: Int -> a -> Vector a -> Vector a
- (//) :: Vector a -> [(Int, a)] -> Vector a
- foldr :: (a -> b -> b) -> b -> Vector a -> b
- foldr' :: (a -> b -> b) -> b -> Vector a -> b
- foldl :: (b -> a -> b) -> b -> Vector a -> b
- foldl' :: (b -> a -> b) -> b -> Vector a -> b
- map :: (a -> b) -> Vector a -> Vector b
- reverse :: Vector a -> Vector a
- takeWhile :: (a -> Bool) -> Vector a -> Vector a
- dropWhile :: (a -> Bool) -> Vector a -> Vector a
- filter :: (a -> Bool) -> Vector a -> Vector a
- partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a)
Documentation
Persistent vectors based on array mapped tries
Instances
Functor Vector Source # | |
Foldable Vector Source # | |
Defined in Data.Vector.Persistent fold :: Monoid m => Vector m -> m # foldMap :: Monoid m => (a -> m) -> Vector a -> m # foldMap' :: Monoid m => (a -> m) -> Vector a -> m # foldr :: (a -> b -> b) -> b -> Vector a -> b # foldr' :: (a -> b -> b) -> b -> Vector a -> b # foldl :: (b -> a -> b) -> b -> Vector a -> b # foldl' :: (b -> a -> b) -> b -> Vector a -> b # foldr1 :: (a -> a -> a) -> Vector a -> a # foldl1 :: (a -> a -> a) -> Vector a -> a # elem :: Eq a => a -> Vector a -> Bool # maximum :: Ord a => Vector a -> a # minimum :: Ord a => Vector a -> a # | |
Traversable Vector Source # | |
Eq a => Eq (Vector a) Source # | |
Ord a => Ord (Vector a) Source # | |
Defined in Data.Vector.Persistent | |
Show a => Show (Vector a) Source # | |
Semigroup (Vector a) Source # | |
Monoid (Vector a) Source # | |
NFData a => NFData (Vector a) Source # | |
Defined in Data.Vector.Persistent |
Construction
append :: Vector a -> Vector a -> Vector a Source #
\( O(m) \) Append two Vector
instances
append v1 v2
This operation is linear in the length of v2
(where length v1 == n
and length v2 == m
).
Queries
Indexing
unsafeIndex :: Vector a -> Int -> a Source #
\( O(1) \) Unchecked indexing into a vector.
Out-of-bounds indexing might not even crash—it will usually just return nonsense values.
Note: the actual lookup is not performed until the result is forced.
This can cause a memory leak if the result of indexing is stored, unforced,
after the rest of the vector becomes garbage. To avoid this, use
unsafeIndexA
or unsafeIndex#
instead.
unsafeIndexA :: Applicative f => Vector a -> Int -> f a Source #
\( O(1) \) Unchecked indexing into a vector in the context of an arbitrary
Applicative
functor. If the Applicative
is "strict" (such as IO
,
(strict) ST s
, (strict) StateT
, or Maybe
, but not Identity
,
ReaderT
, etc.), then the lookup is performed before the next action. This
avoids space leaks that can result from lazy uses of unsafeIndex
. See the
documentation for unsafeIndex#
for a custom Applicative
that can be
especially useful in conjunction with this function.
Note that out-of-bounds indexing might not even crash—it will usually just return nonsense values.
unsafeIndex# :: Vector a -> Int -> (# a #) Source #
\( O(1) \) Unchecked indexing into a vector.
Note that out-of-bounds indexing might not even crash—it will usually just return nonsense values.
This function exists mostly because there is not, as yet, a well-known, canonical, and convenient lifted unary tuple. So we instead offer an eager indexing function returning an unlifted unary tuple. Users who prefer to avoid such "low-level" features can do something like this:
data Solo a = Solo a deriving Functor instance Applicative Solo where pure = Solo liftA2 f (Solo a) (Solo b) = Solo (f a b)
Now
unsafeIndexA :: Vector a -> Int -> Solo a
take :: Int -> Vector a -> Vector a Source #
\( O(n) \) Take n
elements starting from the start of the Vector
drop :: Int -> Vector a -> Vector a Source #
\( O(n) \) Drop n
elements starting from the start of the Vector
splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #
\( O(n) \) Split the vector into two at the given index
Note that this function strictly computes both result vectors (once the tuple itself is reduced to whnf)
slice :: Int -> Int -> Vector a -> Vector a Source #
\( O(n) \) Return a slice of v
of length length
starting at index
start
. The returned vector may have fewer than length
elements
if the bounds are off on either side (the start is negative or
length takes it past the end).
A slice of negative or zero length is the empty vector.
slice start length v
Slicing Storage Management
shrink :: Vector a -> Vector a Source #
\( O(1) \) Drop any unused space in the vector
NOTE: This is currently the identity
Modification
update :: Int -> a -> Vector a -> Vector a Source #
\( O(1) \) Update a single element at ix
with new value elt
in v
.
update ix elt v
(//) :: Vector a -> [(Int, a)] -> Vector a Source #
\( O(n) \) Bulk update.
v // updates
For each (index, element)
pair in updates
, modify v
such that
the index
th position of v
is element
.
Indices in updates
that are not in v
are ignored. The updates are
applied in order, so the last one at each index takes effegct.
Folds
foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #
\( O(n) \) Strict right fold over the vector.
Note: Strict in the initial accumulator value.
foldl' :: (b -> a -> b) -> b -> Vector a -> b Source #
\( O(n) \) Strict left fold over the vector.
Note: Strict in the initial accumulator value.
Transformations
Searches
takeWhile :: (a -> Bool) -> Vector a -> Vector a Source #
\( O(n) \) Apply a predicate p to the vector, returning the longest prefix of elements that satisfy p.