seqn-0.1.1.0: Sequences and measured sequences
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Seqn.MSeq

Description

Finite measured sequences

A value of type MSeq a is a sequence with elements of type a. An MSeq is

  • Spine-strict, hence finite. MSeq cannot represent infinite sequences.
  • Value-strict. It is guaranteed that if an MSeq is in weak head normal form (WHNF), every element of the Seq is also in WHNF.

An MSeq provides quick access to the combined "measure" of all elements of the sequence. Please see the Tutorial at the end of this page for an explanation.

It is recommended to import this module qualified to avoid name clashes.

import Data.Seqn.MSeq (Measured, MSeq)
import qualified Data.Seqn.MSeq as MSeq

Warning

The length of an MSeq must not exceed (maxBound `div` 3) :: Int. If this length is exceeded, the behavior of an MSeq is undefined. This value is very large in practice, greater than \(7 \cdot 10^8\) on 32-bit systems and \(3 \cdot 10^{18}\) on 64-bit systems.

Note on time complexities

Many functions operating on MSeq a require a Measured a constraint. The documented time complexities of these functions assume that measure :: a -> Measure a and (<>) :: Measure a -> Measure a -> Measure a both take \(O(1)\) time. If this not the case, the bounds do not hold. Correct bounds can be calculated by the user depending on their implementations of measure and (<>).

Implementation

MSeq is implemented as a weight-balanced binary tree. This structure is described by

Synopsis

MSeq

data MSeq a Source #

A sequence with elements of type a. An instance of Measured a is required for most operations.

Instances

Instances details
Foldable MSeq Source #
length
\(O(1)\).

Folds are \(O(n)\).

Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

fold :: Monoid m => MSeq m -> m #

foldMap :: Monoid m => (a -> m) -> MSeq a -> m #

foldMap' :: Monoid m => (a -> m) -> MSeq a -> m #

foldr :: (a -> b -> b) -> b -> MSeq a -> b #

foldr' :: (a -> b -> b) -> b -> MSeq a -> b #

foldl :: (b -> a -> b) -> b -> MSeq a -> b #

foldl' :: (b -> a -> b) -> b -> MSeq a -> b #

foldr1 :: (a -> a -> a) -> MSeq a -> a #

foldl1 :: (a -> a -> a) -> MSeq a -> a #

toList :: MSeq a -> [a] #

null :: MSeq a -> Bool #

length :: MSeq a -> Int #

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

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

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

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

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

Eq1 MSeq Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

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

Ord1 MSeq Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

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

Show1 MSeq Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

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

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

FoldableWithIndex Int MSeq Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

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

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

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

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

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

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

Measured a => Monoid (MSeq a) Source #
mempty
The empty sequence.
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

mempty :: MSeq a #

mappend :: MSeq a -> MSeq a -> MSeq a #

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

Measured a => Semigroup (MSeq a) Source #
(<>)
\(O(\left| \log n_1 - \log n_2 \right|)\). Concatenates two sequences.
stimes
\(O(\log c)\). stimes c xs is xs repeating c times. If c < 0, empty is returned.
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

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

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

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

Measured a => IsList (MSeq a) Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Associated Types

type Item (MSeq a) #

Methods

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

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

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

(Measured a, Read a) => Read (MSeq a) Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

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

Defined in Data.Seqn.Internal.MSeq

Methods

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

show :: MSeq a -> String #

showList :: [MSeq a] -> ShowS #

(NFData (Measure a), NFData a) => NFData (MSeq a) Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

rnf :: MSeq a -> () #

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

Defined in Data.Seqn.Internal.MSeq

Methods

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

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

Ord a => Ord (MSeq a) Source #

Lexicographical ordering

Instance details

Defined in Data.Seqn.Internal.MSeq

Methods

compare :: MSeq a -> MSeq a -> Ordering #

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

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

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

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

max :: MSeq a -> MSeq a -> MSeq a #

min :: MSeq a -> MSeq a -> MSeq a #

type Item (MSeq a) Source # 
Instance details

Defined in Data.Seqn.Internal.MSeq

type Item (MSeq a) = a

class Semigroup (Measure a) => Measured a where Source #

Types that have a combinable property, called the measure.

Associated Types

type Measure a Source #

Methods

measure :: a -> Measure a Source #

Calculate the measure of a value.

Instances

Instances details
Ord a => Measured (Elem a) Source # 
Instance details

Defined in Data.Seqn.Internal.PQueue

Associated Types

type Measure (Elem a) Source #

Methods

measure :: Elem a -> Measure (Elem a) Source #

Measured queries

summaryMay :: Measured a => MSeq a -> Maybe (Measure a) Source #

\(O(1)\). The summary is the fold of measures of all elements in the sequence. Returns Nothing if the sequence is empty.

summaryMay == foldMap (Just . measure)

summary :: (Measured a, Monoid (Measure a)) => MSeq a -> Measure a Source #

\(O(1)\). The summary is the fold of measures of all elements in the sequence.

summary == foldMap measure

sliceSummaryMay :: Measured a => (Int, Int) -> MSeq a -> Maybe (Measure a) Source #

\(O(\log n)\). The summary of a slice of the sequence. The slice is indicated by its bounds (inclusive).

sliceSummaryMay lu == summaryMay . slice lu

Since: 0.1.1.0

sliceSummary :: (Measured a, Monoid (Measure a)) => (Int, Int) -> MSeq a -> Measure a Source #

\(O(\log n)\). The summary of a slice of the sequence. The slice is indicated by its bounds (inclusive).

sliceSummary lu == summary . slice lu

Since: 0.1.1.0

foldlSliceSummaryComponents :: Measured a => (b -> Measure a -> b) -> b -> (Int, Int) -> MSeq a -> b Source #

Strict left fold over measures covering a slice. These measures are summaries of \(O(\log n)\) adjacent slices which form the requested slice when concatenated.

foldlSliceSummaryComponents (<>) mempty == sliceSummary

This function is useful when

  • Some property of the summary of a slice is desired.
  • It is expensive to compute the summary, i.e. (<>) for Measure a is expensive.
  • It is possible, and cheaper, to compute the property given components of the summary of the slice.

Examples

Expand

One use case for this is order statistic queries on a slice, such as counting the number of elements less than some value.

It requires a Multiset structure as outlined below, which can be implemented using sorted arrays/balanced binary trees.

data Multiset a
singleton :: Ord a => a -> MultiSet a -- O(1)
(<>) :: Ord a => Multiset a -> Multiset a -> Multiset a -- O(n1 + n2)
countLessThan :: Ord a => a -> Multiset a -> Int -- O(log n)
import Data.Seqn.MSeq (Measured, MSeq)
import qualified Data.Seqn.MSeq as MSeq

newtype Elem a = Elem a deriving Show

instance Ord a => Measured (Elem a) where
  type Measure (Elem a) = Multiset a
  measure (Elem x) = singleton x

-- | O(n log n).
fromList :: Ord a => [a] -> MSeq (Elem a)
fromList = MSeq.fromList . map Elem

-- | O(log^2 n).
countLessThanInSlice :: Ord a => a -> (Int, Int) -> MSeq (Elem a) -> Int
countLessThanInSlice k =
  MSeq.foldlSliceSummaryComponents (\acc xs -> acc + countLessThan k xs) 0

Since: 0.1.1.0

binarySearchPrefix :: Measured a => (Measure a -> Bool) -> MSeq a -> (Maybe Int, Maybe Int) Source #

\(O(\log n)\). Perform a binary search on the summaries of the non-empty prefixes of the sequence.

binarySearchPrefix p xs for a monotonic predicate p returns two adjacent indices i and j, 0 <= i < j < length xs.

  • i is the greatest index such that p (fromJust (summaryMay (take (i+1) xs))) is False, or Nothing if there is no such index.
  • j is the least index such that p (fromJust (summaryMay (take (j+1) xs))) is True, or Nothing if there is no such index.

Examples

Expand
import Data.Monoid (Sum(..))

newtype Elem = E Int deriving Show

instance Measured Elem where
  type Measure Elem = Sum Int
  measure (E x) = Sum x
>>> let xs = fromList [E 1, E 2, E 3, E 4]

The summaries of the prefixes of xs by index are:

  • 0: measure (E 1) = Sum 1.
  • 1: measure (E 1) <> measure (E 2) = Sum 3.
  • 2: measure (E 1) <> measure (E 2) <> measure (E 3) = Sum 6.
  • 3: measure (E 1) <> measure (E 2) <> measure (E 3) <> measure (E 4) = Sum 10.
>>> binarySearchPrefix (> Sum 4) xs
(Just 1,Just 2)
                 ╭──────────┬──────────┬──────────┬──────────╮
index:           │        0 │        1 │        2 │        3 │
                 ├──────────┼──────────┼──────────┼──────────┤
prefix summary:  │    Sum 1 │    Sum 3 │    Sum 6 |   Sum 10 │
                 ├──────────┼──────────┼──────────┼──────────┤
(> Sum 4):       │    False │    False │     True │     True │
                 ╰──────────┴──────────┴──────────┴──────────╯
result:                       ( Just 1 ,   Just 2 )
>>> binarySearchPrefix (> Sum 20) xs
(Just 3,Nothing)
                 ╭──────────┬──────────┬──────────┬──────────╮
index:           │        0 │        1 │        2 │        3 │
                 ├──────────┼──────────┼──────────┼──────────┤
prefix summary:  │    Sum 1 │    Sum 3 │    Sum 6 |   Sum 10 │
                 ├──────────┼──────────┼──────────┼──────────┤
(> Sum 20):      │    False │    False │    False │    False │
                 ╰──────────┴──────────┴──────────┴──────────╯
result:                                             ( Just 3 ,  Nothing )

binarySearchSuffix :: Measured a => (Measure a -> Bool) -> MSeq a -> (Maybe Int, Maybe Int) Source #

\(O(\log n)\). Perform a binary search on the summaries of the non-empty suffixes of the sequence.

binarySearchSuffix p xs for a monotonic predicate p returns two adjacent indices i and j, 0 <= i < j < length xs.

  • i is the greatest index such that p (fromJust (summaryMay (drop i xs))) is True, or Nothing if there is no such index.
  • j is the least index such that p (fromJust (summaryMay (drop j xs))) is False, or Nothing if there is no such index

Examples

Expand
import Data.Monoid (Sum(..))

newtype Elem = E Int deriving Show

instance Measured Elem where
  type Measure Elem = Sum Int
  measure (E x) = Sum x
>>> let xs = fromList [E 1, E 2, E 3, E 4]

The summaries of the suffixes of xs by index are:

  • 0: measure (E 1) <> measure (E 2) <> measure (E 3) <> measure (E 4) = Sum 10.
  • 1: measure (E 2) <> measure (E 3) <> measure (E 4) = Sum 9.
  • 2: measure (E 3) <> measure (E 4) = Sum 7.
  • 3: measure (E 4) = Sum 4.
>>> binarySearchSuffix (> Sum 4) xs
(Just 2,Just 3)
                 ╭──────────┬──────────┬──────────┬──────────╮
index:           │        0 │        1 │        2 │        3 │
                 ├──────────┼──────────┼──────────┼──────────┤
suffix summary:  │   Sum 10 │    Sum 9 │    Sum 7 |    Sum 4 │
                 ├──────────┼──────────┼──────────┼──────────┤
(> Sum 4):       │     True │     True │     True │    False │
                 ╰──────────┴──────────┴──────────┴──────────╯
result:                                  ( Just 2 ,   Just 3 )
>>> binarySearchSuffix (> Sum 20) xs
(Nothing,Just 0)
                          ╭──────────┬──────────┬──────────┬──────────╮
index:                    │        0 │        1 │        2 │        3 │
                          ├──────────┼──────────┼──────────┼──────────┤
suffix summary:           │   Sum 10 │    Sum 9 │    Sum 7 |    Sum 4 │
                          ├──────────┼──────────┼──────────┼──────────┤
(> Sum 20):               │    False │    False │    False │    False │
                          ╰──────────┴──────────┴──────────┴──────────╯
result:         ( Nothing ,   Just 0 )

Construct

empty :: MSeq a Source #

The empty sequence.

singleton :: a -> MSeq a Source #

A singleton sequence.

fromList :: Measured a => [a] -> MSeq a Source #

\(O(n)\). Create an MSeq from a list.

fromRevList :: Measured a => [a] -> MSeq a Source #

\(O(n)\). Create an MSeq from a reversed list.

replicate :: Measured a => Int -> a -> MSeq a Source #

\(O(\log n)\). A sequence with a repeated element. If the length is negative, empty is returned.

replicateA :: (Measured a, Applicative f) => Int -> f a -> f (MSeq a) Source #

\(O(n)\). Generate a sequence from a length and an applicative action. If the length is negative, empty is returned.

generate :: Measured a => Int -> (Int -> a) -> MSeq a Source #

\(O(n)\). Generate a sequence from a length and a generator. If the length is negative, empty is returned.

generateA :: (Measured a, Applicative f) => Int -> (Int -> f a) -> f (MSeq a) Source #

\(O(n)\). Generate a sequence from a length and an applicative generator. If the length is negative, empty is returned.

unfoldr :: Measured a => (b -> Maybe (a, b)) -> b -> MSeq a Source #

\(O(n)\). Unfold a sequence from left to right.

unfoldl :: Measured a => (b -> Maybe (b, a)) -> b -> MSeq a Source #

\(O(n)\). Unfold a sequence from right to left.

unfoldrM :: (Measured a, Monad m) => (b -> m (Maybe (a, b))) -> b -> m (MSeq a) Source #

\(O(n)\). Unfold a sequence monadically from left to right.

unfoldlM :: (Measured a, Monad m) => (b -> m (Maybe (b, a))) -> b -> m (MSeq a) Source #

\(O(n)\). Unfold a sequence monadically from right to left.

concatMap :: (Measured b, Foldable f) => (a -> MSeq b) -> f a -> MSeq b Source #

\(O \left(\sum_i \log n_i \right)\). Map over a Foldable and concatenate the results.

mfix :: Measured a => (a -> MSeq a) -> MSeq a Source #

Monadic fixed point. See Control.Monad.Fix.

Convert

toRevList :: MSeq a -> [a] Source #

\(O(n)\). Convert to a list in reverse.

To convert to a list without reversing, use Data.Foldable.toList.

Index

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

\(O(\log n)\). Look up the element at an index.

index :: Int -> MSeq a -> a Source #

\(O(\log n)\). Look up the element at an index. Calls error if the index is out of bounds.

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

\(O(\log n)\). Infix version of lookup.

(!) :: MSeq a -> Int -> a Source #

\(O(\log n)\). Infix version of index. Calls error if the index is out of bounds.

update :: Measured a => Int -> a -> MSeq a -> MSeq a Source #

\(O(\log n)\). Update an element at an index. If the index is out of bounds, the sequence is returned unchanged.

adjust :: Measured a => (a -> a) -> Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Adjust the element at an index. If the index is out of bounds, the sequence is returned unchanged.

insertAt :: Measured a => Int -> a -> MSeq a -> MSeq a Source #

\(O(\log n)\). Insert an element at an index. If the index is out of bounds, the element is added to the closest end of the sequence.

deleteAt :: Measured a => Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Delete an element at an index. If the index is out of bounds, the sequence is returned unchanged.

Slice

cons :: Measured a => a -> MSeq a -> MSeq a Source #

\(O(\log n)\). Append a value to the beginning of a sequence.

snoc :: Measured a => MSeq a -> a -> MSeq a Source #

\(O(\log n)\). Append a value to the end of a sequence.

uncons :: Measured a => MSeq a -> Maybe (a, MSeq a) Source #

\(O(\log n)\). The head and tail of a sequence.

unsnoc :: Measured a => MSeq a -> Maybe (MSeq a, a) Source #

\(O(\log n)\). The init and last of a sequence.

take :: Measured a => Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Take a number of elements from the beginning of a sequence.

drop :: Measured a => Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Drop a number of elements from the beginning of a sequence.

slice :: Measured a => (Int, Int) -> MSeq a -> MSeq a Source #

\(O(\log n)\). The slice of a sequence between two indices (inclusive).

splitAt :: Measured a => Int -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(\log n)\). Split a sequence at a given index.

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

takeEnd :: Measured a => Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Take a number of elements from the end of a sequence.

dropEnd :: Measured a => Int -> MSeq a -> MSeq a Source #

\(O(\log n)\). Drop a number of elements from the end of a sequence.

splitAtEnd :: Measured a => Int -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(\log n)\). Split a sequence at a given index from the end.

splitAtEnd n xs == (dropEnd n xs, takeEnd n xs)

Filter

filter :: Measured a => (a -> Bool) -> MSeq a -> MSeq a Source #

\(O(n)\). Keep elements that satisfy a predicate.

mapMaybe :: Measured b => (a -> Maybe b) -> MSeq a -> MSeq b Source #

\(O(n)\). Map over elements and collect the Justs.

mapEither :: (Measured b, Measured c) => (a -> Either b c) -> MSeq a -> (MSeq b, MSeq c) Source #

\(O(n)\). Map over elements and split the Lefts and Rights.

filterA :: (Measured a, Applicative f) => (a -> f Bool) -> MSeq a -> f (MSeq a) Source #

\(O(n)\). Keep elements that satisfy an applicative predicate.

mapMaybeA :: (Measured b, Applicative f) => (a -> f (Maybe b)) -> MSeq a -> f (MSeq b) Source #

\(O(n)\). Traverse over elements and collect the Justs.

mapEitherA :: (Measured b, Measured c, Applicative f) => (a -> f (Either b c)) -> MSeq a -> f (MSeq b, MSeq c) Source #

\(O(n)\). Traverse over elements and split the Lefts and Rights.

takeWhile :: Measured a => (a -> Bool) -> MSeq a -> MSeq a Source #

\(O(i + \log n)\). The longest prefix of elements that satisfy a predicate. \(i\) is the length of the prefix.

dropWhile :: Measured a => (a -> Bool) -> MSeq a -> MSeq a Source #

\(O(i + \log n)\). The remainder after removing the longest prefix of elements that satisfy a predicate. \(i\) is the length of the prefix.

span :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(i + \log n)\). The longest prefix of elements that satisfy a predicate, together with the remainder of the sequence. \(i\) is the length of the prefix.

span p xs == (takeWhile p xs, dropWhile p xs)

break :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(i + \log n)\). The longest prefix of elements that do not satisfy a predicate, together with the remainder of the sequence. \(i\) is the length of the prefix.

break p == span (not . p)

takeWhileEnd :: Measured a => (a -> Bool) -> MSeq a -> MSeq a Source #

\(O(i + \log n)\). The longest suffix of elements that satisfy a predicate. \(i\) is the length of the suffix.

dropWhileEnd :: Measured a => (a -> Bool) -> MSeq a -> MSeq a Source #

\(O(i + \log n)\). The remainder after removing the longest suffix of elements that satisfy a predicate. \(i\) is the length of the suffix.

spanEnd :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(i + \log n)\). The longest suffix of elements that satisfy a predicate, together with the remainder of the sequence. \(i\) is the length of the suffix.

spanEnd p xs == (dropWhileEnd p xs, takeWhileEnd p xs)

breakEnd :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a) Source #

\(O(i + \log n)\). The longest suffix of elements that do not satisfy a predicate, together with the remainder of the sequence. \(i\) is the length of the suffix.

breakEnd p == spanEnd (not . p)

Transform

map :: Measured b => (a -> b) -> MSeq a -> MSeq b Source #

\(O(n)\). Map over a sequence.

liftA2 :: Measured c => (a -> b -> c) -> MSeq a -> MSeq b -> MSeq c Source #

\(O(n_1 n_2)\). Cartesian product of two sequences.

traverse :: (Measured b, Applicative f) => (a -> f b) -> MSeq a -> f (MSeq b) Source #

\(O(n)\). Traverse a sequence.

imap :: Measured b => (Int -> a -> b) -> MSeq a -> MSeq b Source #

\(O(n)\). Map over a sequence with index.

itraverse :: (Measured b, Applicative f) => (Int -> a -> f b) -> MSeq a -> f (MSeq b) Source #

\(O(n)\). Traverse a sequence with index.

reverse :: Measured a => MSeq a -> MSeq a Source #

\(O(n)\). Reverse a sequence.

intersperse :: Measured a => a -> MSeq a -> MSeq a Source #

\(O(n)\). Intersperse an element between the elements of a sequence.

scanl :: Measured b => (b -> a -> b) -> b -> MSeq a -> MSeq b Source #

\(O(n)\). Like foldl' but keeps all intermediate values.

scanr :: Measured b => (a -> b -> b) -> b -> MSeq a -> MSeq b Source #

\(O(n)\). Like foldr' but keeps all intermediate values.

sort :: (Ord a, Measured a) => MSeq a -> MSeq a Source #

\(O(n \log n)\). Sort a sequence.

sortBy :: Measured a => (a -> a -> Ordering) -> MSeq a -> MSeq a Source #

\(O(n \log n)\). Sort a sequence using a comparison function.

Search and test

findEnd :: (a -> Bool) -> MSeq a -> Maybe a Source #

\(O(n)\). The last element satisfying a predicate.

To get the first element, use Data.Foldable.find.

findIndex :: (a -> Bool) -> MSeq a -> Maybe Int Source #

\(O(n)\). The index of the first element satisfying a predicate.

findIndexEnd :: (a -> Bool) -> MSeq a -> Maybe Int Source #

\(O(n)\). The index of the last element satisfying a predicate.

infixIndices :: Eq a => MSeq a -> MSeq a -> [Int] Source #

\(O(n_1 + n_2)\). Indices in the second sequence where the first sequence begins as a substring. Includes overlapping occurences.

binarySearchFind :: (a -> Ordering) -> MSeq a -> Maybe a Source #

\(O(\log n)\). Binary search for an element in a sequence.

Given a function f this function returns an arbitrary element x, if it exists, such that f x = EQ. f must be monotonic on the sequence— specifically fmap f must result in a sequence which has many (possibly zero) LTs, followed by many EQs, followed by many GTs.

isPrefixOf :: Eq a => MSeq a -> MSeq a -> Bool Source #

\(O(\min(n_1,n_2))\). Whether the first sequence is a prefix of the second.

isSuffixOf :: Eq a => MSeq a -> MSeq a -> Bool Source #

\(O(\min(n_1,n_2))\). Whether the first sequence is a suffix of the second.

isInfixOf :: Eq a => MSeq a -> MSeq a -> Bool Source #

\(O(n_1 + n_2)\). Whether the first sequence is a substring of the second.

isSubsequenceOf :: Eq a => MSeq a -> MSeq a -> Bool Source #

\(O(n_1 + n_2)\). Whether the first sequence is a subsequence of the second.

Zip and unzip

zipWith :: Measured c => (a -> b -> c) -> MSeq a -> MSeq b -> MSeq c Source #

\(O(\min(n_1,n_2))\). Zip two sequences with a function. The result is as long as the shorter sequence.

zipWith3 :: Measured d => (a -> b -> c -> d) -> MSeq a -> MSeq b -> MSeq c -> MSeq d Source #

\(O(\min(n_1,n_2,n_3))\). Zip three sequences with a function. The result is as long as the shortest sequence.

zipWithM :: (Measured c, Monad m) => (a -> b -> m c) -> MSeq a -> MSeq b -> m (MSeq c) Source #

\(O(\min(n_1,n_2))\). Zip two sequences with a monadic function.

zipWith3M :: (Measured d, Monad m) => (a -> b -> c -> m d) -> MSeq a -> MSeq b -> MSeq c -> m (MSeq d) Source #

\(O(\min(n_1,n_2,n_3))\). Zip three sequences with a monadic function.

unzipWith :: (Measured b, Measured c) => (a -> (b, c)) -> MSeq a -> (MSeq b, MSeq c) Source #

\(O(n)\). Map over a sequence and unzip the result.

unzipWith3 :: (Measured b, Measured c, Measured d) => (a -> (b, c, d)) -> MSeq a -> (MSeq b, MSeq c, MSeq d) Source #

\(O(n)\). Map over a sequence and unzip the result.

Force

liftRnf2 :: (Measure a -> ()) -> (a -> ()) -> MSeq a -> () Source #

Reduce a sequence to normal form, given functions to reduce its contents.

Tutorial

MSeq, like Seq, is a sequence which supports operations like lookup, splitAt, (<>), foldr, and more.

Additionally, every element in an MSeq has an associated "measure". Such measures can be combined using a Semigroup instance. An MSeq allows accessing the combined measure of all its elements in \(O(1)\) time. The choice of the measure depends on the use case.

Example 1: Sum

data Task = Task
  !Text -- ^ Name
  !Word -- ^ Cost
  deriving Show

Consider that we need to maintain a sequence of tasks, where each task has some cost. Tasks will be added and removed over time. At various points, the total cost of all the tasks in the sequence must be computed.

We may use a Seq to store the task, and calculate the sum when required in \(O(n)\). This is reasonable if such events are rare, but a poor strategy if the sum has to be calculated frequently. In the latter case, we could use an MSeq.

First, some imports.

import Data.Seqn.MSeq (Measured, MSeq)
import qualified Data.Seqn.MSeq as MSeq

Next, we define the Measured instance for Task.

{-# LANGUAGE TypeFamilies #-}
import Data.Monoid (Sum(..))

instance Measured Task where
  type Measure Task = Sum Word
  measure (Task _ cost) = Sum cost
>>> let tasks = MSeq.fromList [Task "A" 50, Task "B" 30, Task "C" 60]
>>> tasks
[Task "A" 50,Task "B" 30,Task "C" 60]

We now have access to the combined measure of the MSeq, called the summary, in \(O(1)\).

>>> MSeq.summary tasks
Sum {getSum = 140}

If we modify the task list, the summary will change accordingly.

>>> let tasks' = MSeq.deleteAt 2 $ MSeq.cons (Task "D" 100) tasks
>>> tasks'
[Task "D" 100,Task "A" 50,Task "C" 60]
>>> MSeq.summary tasks'
Sum {getSum = 210}

Example 2: Max

Consider that we now need the maximum cost instead of the sum, or both sum and max. We need only change the Measured instance to use another Semigroup that fits the requirement.

data SumMax = SumMax
  { sum_ :: !Word
  , max_ :: !Word
  } deriving Show

instance Semigroup SumMax where
  SumMax sum1 max1 <> SumMax sum2 max2 =
    SumMax (sum1+sum2) (max max1 max2)

instance Measured Task where
  type Measure Task = SumMax
  measure (Task _ cost) = SumMax cost cost

We can see that it works as expected.

>>> let tasks = MSeq.fromList [Task "A" 50, Task "B" 30, Task "C" 60]
>>> MSeq.summaryMay tasks
Just (SumMax {sum_ = 140, max_ = 60})

Note that we used summaryMay instead of summary, since we did not define a monoid instance for SumMax.

Aside: For the above scenario you may have considered using (Sum Word, Max Word) as the measure, since the Semigroup instance for it is already defined. While that would work, it would be inefficient because (a,b) and its (<>) implementation are lazy in a and b.

Example 3: Binary search

Consider that there are events where we unlock the ability to process tasks with a total cost \(c\). To handle such events, we need to split out the maximum number of tasks from the beginning of the sequence such that their total does not exceed \(c\), and send them for processing.

We can do this efficiently with an MSeq. The prefix sums of costs, which is a component of our measure, forms a monotonic non-decreasing sequence. We can take advantage of this and use binary search to find the point where the sequence should be split.

splitAtMost :: Word -> MSeq Task -> Maybe (MSeq Task, MSeq Task)
splitAtMost c tasks =
  case MSeq.binarySearchPrefix (\(SumMax c' _) -> c' > c) tasks of
    (Nothing, _) -> Nothing -- c is too small for even the first task
    (Just i, _) -> Just $! MSeq.splitAt (i+1) tasks
>>> let tasks = MSeq.fromList [Task "A" 50, Task "B" 30, Task "C" 60]
>>> splitAtMost 100 tasks
Just ([Task "A" 50,Task "B" 30],[Task "C" 60])
>>> splitAtMost 10 tasks
Nothing

The running time of splitAtMost is simply \(O(\log n)\), and it does not depend on how many tasks are split out.

More uses

More uses of measured sequences can be found in the paper on finger trees:

One such use, priority queues, is implemented in this package and can be found in the module Data.Seqn.PQueue.