persistent-vector-0.2.0: A persistent sequence based on array mapped tries
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Persistent

Description

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

Documentation

data Vector a Source #

Persistent vectors based on array mapped tries

Instances

Instances details
Functor Vector Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

fmap :: (a -> b) -> Vector a -> Vector b #

(<$) :: a -> Vector b -> Vector a #

Foldable Vector Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

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 #

toList :: Vector a -> [a] #

null :: Vector a -> Bool #

length :: Vector a -> Int #

elem :: Eq a => a -> Vector a -> Bool #

maximum :: Ord a => Vector a -> a #

minimum :: Ord a => Vector a -> a #

sum :: Num a => Vector a -> a #

product :: Num a => Vector a -> a #

Traversable Vector Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

traverse :: Applicative f => (a -> f b) -> Vector a -> f (Vector b) #

sequenceA :: Applicative f => Vector (f a) -> f (Vector a) #

mapM :: Monad m => (a -> m b) -> Vector a -> m (Vector b) #

sequence :: Monad m => Vector (m a) -> m (Vector a) #

Eq a => Eq (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

(==) :: Vector a -> Vector a -> Bool #

(/=) :: Vector a -> Vector a -> Bool #

Ord a => Ord (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

compare :: Vector a -> Vector a -> Ordering #

(<) :: Vector a -> Vector a -> Bool #

(<=) :: Vector a -> Vector a -> Bool #

(>) :: Vector a -> Vector a -> Bool #

(>=) :: Vector a -> Vector a -> Bool #

max :: Vector a -> Vector a -> Vector a #

min :: Vector a -> Vector a -> Vector a #

Show a => Show (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Semigroup (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

(<>) :: Vector a -> Vector a -> Vector a #

sconcat :: NonEmpty (Vector a) -> Vector a #

stimes :: Integral b => b -> Vector a -> Vector a #

Monoid (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

mempty :: Vector a #

mappend :: Vector a -> Vector a -> Vector a #

mconcat :: [Vector a] -> Vector a #

NFData a => NFData (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent

Methods

rnf :: Vector a -> () #

Construction

empty :: Vector a Source #

\( O(1) \) The empty vector.

singleton :: a -> Vector a Source #

\( O(1) \) Construct a vector with a single element.

snoc :: Vector a -> a -> Vector a Source #

\( O(1) \) Append an element to the end of the vector.

fromList :: [a] -> Vector a Source #

\( O(n) \) Construct a vector from a list

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

null :: Vector a -> Bool Source #

\( O(1) \) Test to see if the vector is empty.

length :: Vector a -> Int Source #

\( O(1) \) Get the length of the vector.

Indexing

index :: Vector a -> Int -> Maybe a Source #

\( O(1) \) Bounds-checked indexing into a vector.

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 indexth 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) \) Right fold over the vector

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) \) Left fold over the vector.

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

map :: (a -> b) -> Vector a -> Vector b Source #

\( O(n) \) Map over the vector

reverse :: Vector a -> Vector a Source #

\( O(n) \) Reverse a vector

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.

dropWhile :: (a -> Bool) -> Vector a -> Vector a Source #

\( O(n) \) Returns the longest suffix after takeWhile p v.

filter :: (a -> Bool) -> Vector a -> Vector a Source #

\( O(n) \) Filter according to the predicate.

partition :: (a -> Bool) -> Vector a -> (Vector a, Vector a) Source #

\( O(n) \) Return the elements that do and do not obey the predicate