rrb-vector-0.1.0.0: Efficient RRB-Vectors
Safe HaskellNone
LanguageHaskell2010

Data.RRBVector

Description

The Vector a type is an RRB-Vector of elements of type a.

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

Performance

The worst case running time complexities are given, with \(n\) referring to the number of elements in the vector (or \(n_1\), \(n_2\), etc. for multiple vectors). Note that all logarithms are base 16, so the constant factor for \(O(\log n)\) operations is quite small.

Implementation

The implementation uses Relaxed-Radix-Balanced trees, as described by

Currently, a branching factor of 16 is used. The tree is strict in its spine, but lazy in its elements.

Synopsis

Documentation

data Vector a Source #

A vector.

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

Instances

Instances details
Monad Vector Source # 
Instance details

Defined in Data.RRBVector.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.RRBVector.Internal

Methods

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

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

MonadFix Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

MonadFail Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

fail :: String -> Vector a #

Applicative Vector Source # 
Instance details

Defined in Data.RRBVector.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.RRBVector.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.RRBVector.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) #

Eq1 Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

Ord1 Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

Read1 Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Vector a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Vector a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Vector a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Vector a] #

Show1 Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

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

MonadZip Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

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

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

Alternative Vector Source # 
Instance details

Defined in Data.RRBVector.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.RRBVector.Internal

Methods

mzero :: Vector a #

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

NFData1 Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

FunctorWithIndex Int Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

FoldableWithIndex Int Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Vector a -> m #

ifoldMap' :: Monoid m => (Int -> a -> m) -> Vector a -> m #

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

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

ifoldr' :: (Int -> a -> b -> b) -> b -> Vector a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Vector a -> b #

TraversableWithIndex Int Vector Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

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

IsList (Vector a) Source # 
Instance details

Defined in Data.RRBVector.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.RRBVector.Internal

Methods

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

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

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

Defined in Data.RRBVector.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 #

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

Defined in Data.RRBVector.Internal

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

Defined in Data.RRBVector.Internal

Methods

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

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

a ~ Char => IsString (Vector a) Source # 
Instance details

Defined in Data.RRBVector.Internal

Methods

fromString :: String -> Vector a #

Semigroup (Vector a) Source # 
Instance details

Defined in Data.RRBVector.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.RRBVector.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.RRBVector.Internal

Methods

rnf :: Vector a -> () #

type Item (Vector a) Source # 
Instance details

Defined in Data.RRBVector.Internal

type Item (Vector a) = a

Construction

empty :: Vector a Source #

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

empty = fromList []

singleton :: a -> Vector a Source #

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

singleton x = fromList [x]

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

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

Concatenation

(<|) :: a -> Vector a -> Vector a infixr 5 Source #

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

>>> 1 <| fromList [2, 3, 4]
fromList [1,2,3,4]

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

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

>>> fromList [1, 2, 3] |> 4
fromList [1,2,3,4]

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

\(O(\log \max(n_1, n_2))\). Concatenates two vectors.

>>> fromList [1, 2, 3] >< fromList [4, 5]
fromList [1,2,3,4,5]

Deconstruction

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

\(O(\log n)\). The first element and the vector without the first element, or Nothing if the vector is empty.

>>> viewl (fromList [1, 2, 3])
Just (1,fromList [2,3])

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

\(O(\log n)\). The vector without the last element and the last element, or Nothing if the vector is empty.

>>> viewr (fromList [1, 2, 3])
Just (fromList [1,2],3)

Indexing

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)\). Update the element at the index with a new element. If the index is out of range, the original vector is returned.

adjust :: Int -> (a -> a) -> 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.

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

\(O(\log n)\). Like adjust, but the result of the function is forced.

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

\(O(\log n)\). The first i elements of the vector. If i is negative, the empty vector is returned. If the vector contains less than i elements, the whole vector is returned.

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

\(O(\log n)\). The vector without the first i elements If i is negative, the whole vector is returned. If the vector contains less than i elements, the empty vector is returned.

splitAt :: Int -> Vector a -> (Vector a, Vector a) Source #

\(O(\log n)\). Split the vector at the given index.

splitAt n v = (take n v, drop n v)

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

\(O(\log n)\). Insert an element at the given index.

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

\(O(\log n)\). Delete the element at the given index.

With Index

Reexported from indexed-traversable.

Transformations

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

\(O(n)\). Apply the function to every element.

>>> map (+ 1) (fromList [1, 2, 3])
fromList [2,3,4]

reverse :: Vector a -> Vector a Source #

\(O(n)\). Reverse the vector.

>>> reverse (fromList [1, 2, 3])
fromList [3,2,1]

Zipping and unzipping

zip :: Vector a -> Vector b -> Vector (a, b) Source #

\(O(\min(n_1, n_2))\). Take two vectors and return a vector of corresponding pairs. If one input is longer, excess elements are discarded from the right end.

zip = zipWith (,)

zipWith :: (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

\(O(\min(n_1, n_2))\). zipWith generalizes zip by zipping with the function.

unzip :: Vector (a, b) -> (Vector a, Vector b) Source #

\(O(n)\). Unzip a vector of pairs.

>>> unzip (fromList [(1, "a"), (2, "b"), (3, "c")])
(fromList [1,2,3],fromList ["a","b","c"])