pvector-0.1.0.0: Fast persistent vectors
Safe HaskellNone
LanguageHaskell2010

Data.Vector.Persistent

Description

The Vector a type is an persistent vector of elements of type a.

This module should be imported qualified, to avoid name clashes with the Prelude.

Many operations have a average-case complexity of O(log n). The implementation uses a large base (i.e. 32) so in practice these operations are constant time.

Comparison with Data.RRBVector and Data.Sequence

  • Persistent vectors generally have less operations than sequences or RRBVectors but those operations can be faster.
  • Persistent vectors have the fastest indexing.
  • Persistent vectors are faster than RRBVectors at snocing because of tail optimization. Snocing is a near constant time operation. Snocing is still slower than sequences.
  • RRBVectors are faster than persistent vectors at splitting and merging, but still slower than sequences.
  • RRBVectors are faster than Sequences at indexing but slower than persistent vectors.
  • Sequences have the fastest consing, snocing, and merging, but the slowest indexing.

Synopsis

Documentation

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

\(O(n)\) Lazy right fold.

foldr' :: (a -> b -> b) -> b -> Vector a -> b Source #

\(O(n)\) Strict right fold.

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

\(O(n)\) Lazy left fold.

foldl' :: (b -> a -> b) -> b -> Vector a -> b Source #

\(O(n)\) Strict left fold.

data Vector a where Source #

A vector.

The instances are based on those of Seqs, which are in turn based on those of lists.

Bundled Patterns

pattern (:|>) :: Vector a -> a -> Vector a infixl 5

\(O(\log n)\). A bidirectional pattern synonym viewing the rear of a non-empty sequence.

pattern Empty :: Vector a

\(O(1)\). A bidirectional pattern synonym matching an empty sequence.

Instances

Instances details
Monad Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

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

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

return :: a -> Vector a #

Functor Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

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

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

MonadFail Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

fail :: String -> Vector a #

Applicative Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

pure :: a -> Vector a #

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

liftA2 :: (a -> b -> c) -> Vector a -> Vector b -> Vector c #

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

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

Foldable Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

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.Internal

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) #

Show1 Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Vector a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Vector a] -> ShowS #

Alternative Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

empty :: Vector a #

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

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

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

MonadPlus Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

mzero :: Vector a #

mplus :: Vector a -> Vector a -> Vector a #

NFData1 Vector Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Methods

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

IsList (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

Associated Types

type Item (Vector a) #

Methods

fromList :: [Item (Vector a)] -> Vector a #

fromListN :: Int -> [Item (Vector a)] -> Vector a #

toList :: Vector a -> [Item (Vector a)] #

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

Defined in Data.Vector.Persistent.Internal

Methods

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

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

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

Defined in Data.Vector.Persistent.Internal

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.Internal

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.Internal

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.Internal

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.Internal

Methods

rnf :: Vector a -> () #

type Item (Vector a) Source # 
Instance details

Defined in Data.Vector.Persistent.Internal

type Item (Vector a) = a

(|>) :: Vector a -> a -> Vector a Source #

\(O(\log n)\). An alias for snoc Mnemonic: a triangle with the single element at the pointy end.

empty :: Vector a Source #

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

length :: Vector a -> Int Source #

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

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

\(O(\log n)\). The element at the index or Nothing if the index is out of range.

index :: HasCallStack => Int -> Vector a -> a Source #

\(O(\log n)\). The element at the index. Calls error if the index is out of range.

(!?) :: Vector a -> Int -> Maybe a Source #

\(O(\log n)\). A flipped version of lookup.

(!) :: HasCallStack => Vector a -> Int -> a Source #

\(O(\log n)\). A flipped version of index.

update :: Int -> a -> Vector a -> Vector a Source #

\(O(\log n)\). Replace the element at the specified position. If the position is out of range, the original sequence is returned.

adjust :: (a -> a) -> Int -> Vector a -> Vector a Source #

\(O(\log n)\). Adjust the element at the index by applying the function to it. If the index is out of range, the original vector is returned.

adjustF :: Applicative f => (a -> f a) -> Int -> Vector a -> f (Vector a) Source #

\(O(\log n)\). Same as adjust but can have effects through Applicative

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

\(O(\log n)\) Add an element to the end of the vector.

singleton :: a -> Vector a Source #

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

null :: Vector a -> Bool Source #

\(O(1)\) Return True if the vector is empty, False otherwise.

(//) :: Vector a -> [(Int, a)] -> Vector a Source #

\(O(n)\). For each pair (i,a) from the vector of index/value pairs, replace the vector element at position i by a.

update <5,9,2,7> <(2,1),(0,3),(2,8)> = <3,9,8,7>

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

\(O(n)\). Concatenate two vectors.

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

\(O(n)\). Apply a function to all values in the vector.

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

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

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

\(O(n)\). Create a vector from a list.

unsnoc :: Vector a -> Maybe (Vector a, a) Source #

\(O(\log n)\). Decompose a list into its head and tail.

  • If the list is empty, returns Nothing.
  • If the list is non-empty, returns Just (x, xs), where x is the head of the list and xs its tail.