Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 theSeq
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
- J. Nievergelt and E. M. Reingold, "Binary search trees of bounded balance", SIAM Journal of Computing 2(1), 1973, https://doi.org/10.1137/0202005
- Stephen Adams, "Efficient sets—a balancing act", Journal of Functional Programming 3(4), 553-561, 1993, https://doi.org/10.1017/S0956796800000885
- Yoichi Hirai and Kazuhiko Yamamoto, "Balancing weight-balanced trees", Journal of Functional Programming 21(3), 287-307, 2011, https://doi.org/10.1017/S0956796811000104
- Guy Blelloch, Daniel Ferizovic, and Yihan Sun, "Parallel Ordered Sets Using Join", 2016, https://doi.org/10.48550/arXiv.1602.02120
Synopsis
- data MSeq a
- class Semigroup (Measure a) => Measured a where
- summaryMay :: Measured a => MSeq a -> Maybe (Measure a)
- summary :: (Measured a, Monoid (Measure a)) => MSeq a -> Measure a
- sliceSummaryMay :: Measured a => (Int, Int) -> MSeq a -> Maybe (Measure a)
- sliceSummary :: (Measured a, Monoid (Measure a)) => (Int, Int) -> MSeq a -> Measure a
- foldlSliceSummaryComponents :: Measured a => (b -> Measure a -> b) -> b -> (Int, Int) -> MSeq a -> b
- binarySearchPrefix :: Measured a => (Measure a -> Bool) -> MSeq a -> (Maybe Int, Maybe Int)
- binarySearchSuffix :: Measured a => (Measure a -> Bool) -> MSeq a -> (Maybe Int, Maybe Int)
- empty :: MSeq a
- singleton :: a -> MSeq a
- fromList :: Measured a => [a] -> MSeq a
- fromRevList :: Measured a => [a] -> MSeq a
- replicate :: Measured a => Int -> a -> MSeq a
- replicateA :: (Measured a, Applicative f) => Int -> f a -> f (MSeq a)
- generate :: Measured a => Int -> (Int -> a) -> MSeq a
- generateA :: (Measured a, Applicative f) => Int -> (Int -> f a) -> f (MSeq a)
- unfoldr :: Measured a => (b -> Maybe (a, b)) -> b -> MSeq a
- unfoldl :: Measured a => (b -> Maybe (b, a)) -> b -> MSeq a
- unfoldrM :: (Measured a, Monad m) => (b -> m (Maybe (a, b))) -> b -> m (MSeq a)
- unfoldlM :: (Measured a, Monad m) => (b -> m (Maybe (b, a))) -> b -> m (MSeq a)
- concatMap :: (Measured b, Foldable f) => (a -> MSeq b) -> f a -> MSeq b
- mfix :: Measured a => (a -> MSeq a) -> MSeq a
- toRevList :: MSeq a -> [a]
- lookup :: Int -> MSeq a -> Maybe a
- index :: Int -> MSeq a -> a
- (!?) :: MSeq a -> Int -> Maybe a
- (!) :: MSeq a -> Int -> a
- update :: Measured a => Int -> a -> MSeq a -> MSeq a
- adjust :: Measured a => (a -> a) -> Int -> MSeq a -> MSeq a
- insertAt :: Measured a => Int -> a -> MSeq a -> MSeq a
- deleteAt :: Measured a => Int -> MSeq a -> MSeq a
- cons :: Measured a => a -> MSeq a -> MSeq a
- snoc :: Measured a => MSeq a -> a -> MSeq a
- uncons :: Measured a => MSeq a -> Maybe (a, MSeq a)
- unsnoc :: Measured a => MSeq a -> Maybe (MSeq a, a)
- take :: Measured a => Int -> MSeq a -> MSeq a
- drop :: Measured a => Int -> MSeq a -> MSeq a
- slice :: Measured a => (Int, Int) -> MSeq a -> MSeq a
- splitAt :: Measured a => Int -> MSeq a -> (MSeq a, MSeq a)
- takeEnd :: Measured a => Int -> MSeq a -> MSeq a
- dropEnd :: Measured a => Int -> MSeq a -> MSeq a
- splitAtEnd :: Measured a => Int -> MSeq a -> (MSeq a, MSeq a)
- filter :: Measured a => (a -> Bool) -> MSeq a -> MSeq a
- mapMaybe :: Measured b => (a -> Maybe b) -> MSeq a -> MSeq b
- mapEither :: (Measured b, Measured c) => (a -> Either b c) -> MSeq a -> (MSeq b, MSeq c)
- filterA :: (Measured a, Applicative f) => (a -> f Bool) -> MSeq a -> f (MSeq a)
- mapMaybeA :: (Measured b, Applicative f) => (a -> f (Maybe b)) -> MSeq a -> f (MSeq b)
- mapEitherA :: (Measured b, Measured c, Applicative f) => (a -> f (Either b c)) -> MSeq a -> f (MSeq b, MSeq c)
- takeWhile :: Measured a => (a -> Bool) -> MSeq a -> MSeq a
- dropWhile :: Measured a => (a -> Bool) -> MSeq a -> MSeq a
- span :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a)
- break :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a)
- takeWhileEnd :: Measured a => (a -> Bool) -> MSeq a -> MSeq a
- dropWhileEnd :: Measured a => (a -> Bool) -> MSeq a -> MSeq a
- spanEnd :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a)
- breakEnd :: Measured a => (a -> Bool) -> MSeq a -> (MSeq a, MSeq a)
- map :: Measured b => (a -> b) -> MSeq a -> MSeq b
- liftA2 :: Measured c => (a -> b -> c) -> MSeq a -> MSeq b -> MSeq c
- traverse :: (Measured b, Applicative f) => (a -> f b) -> MSeq a -> f (MSeq b)
- imap :: Measured b => (Int -> a -> b) -> MSeq a -> MSeq b
- itraverse :: (Measured b, Applicative f) => (Int -> a -> f b) -> MSeq a -> f (MSeq b)
- reverse :: Measured a => MSeq a -> MSeq a
- intersperse :: Measured a => a -> MSeq a -> MSeq a
- scanl :: Measured b => (b -> a -> b) -> b -> MSeq a -> MSeq b
- scanr :: Measured b => (a -> b -> b) -> b -> MSeq a -> MSeq b
- sort :: (Ord a, Measured a) => MSeq a -> MSeq a
- sortBy :: Measured a => (a -> a -> Ordering) -> MSeq a -> MSeq a
- findEnd :: (a -> Bool) -> MSeq a -> Maybe a
- findIndex :: (a -> Bool) -> MSeq a -> Maybe Int
- findIndexEnd :: (a -> Bool) -> MSeq a -> Maybe Int
- infixIndices :: Eq a => MSeq a -> MSeq a -> [Int]
- binarySearchFind :: (a -> Ordering) -> MSeq a -> Maybe a
- isPrefixOf :: Eq a => MSeq a -> MSeq a -> Bool
- isSuffixOf :: Eq a => MSeq a -> MSeq a -> Bool
- isInfixOf :: Eq a => MSeq a -> MSeq a -> Bool
- isSubsequenceOf :: Eq a => MSeq a -> MSeq a -> Bool
- zipWith :: Measured c => (a -> b -> c) -> MSeq a -> MSeq b -> MSeq c
- zipWith3 :: Measured d => (a -> b -> c -> d) -> MSeq a -> MSeq b -> MSeq c -> MSeq d
- zipWithM :: (Measured c, Monad m) => (a -> b -> m c) -> MSeq a -> MSeq b -> m (MSeq c)
- zipWith3M :: (Measured d, Monad m) => (a -> b -> c -> m d) -> MSeq a -> MSeq b -> MSeq c -> m (MSeq d)
- unzipWith :: (Measured b, Measured c) => (a -> (b, c)) -> MSeq a -> (MSeq b, MSeq c)
- unzipWith3 :: (Measured b, Measured c, Measured d) => (a -> (b, c, d)) -> MSeq a -> (MSeq b, MSeq c, MSeq d)
- liftRnf2 :: (Measure a -> ()) -> (a -> ()) -> MSeq a -> ()
MSeq
A sequence with elements of type a
. An instance of
is
required for most operations.Measured
a
Instances
Foldable MSeq Source # |
Folds are \(O(n)\). |
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 # elem :: Eq a => a -> MSeq a -> Bool # maximum :: Ord a => MSeq a -> a # | |
Eq1 MSeq Source # | |
Ord1 MSeq Source # | |
Defined in Data.Seqn.Internal.MSeq | |
Show1 MSeq Source # | |
FoldableWithIndex Int MSeq Source # | |
Defined in Data.Seqn.Internal.MSeq | |
Measured a => Monoid (MSeq a) Source # |
|
Measured a => Semigroup (MSeq a) Source # |
|
Measured a => IsList (MSeq a) Source # | |
(Measured a, Read a) => Read (MSeq a) Source # | |
Show a => Show (MSeq a) Source # | |
(NFData (Measure a), NFData a) => NFData (MSeq a) Source # | |
Defined in Data.Seqn.Internal.MSeq | |
Eq a => Eq (MSeq a) Source # | |
Ord a => Ord (MSeq a) Source # | Lexicographical ordering |
type Item (MSeq a) Source # | |
Defined in Data.Seqn.Internal.MSeq |
class Semigroup (Measure a) => Measured a where Source #
Types that have a combinable property, called the measure.
Measured queries
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
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.
(<>)
forMeasure a
is expensive. - It is possible, and cheaper, to compute the property given components of the summary of the slice.
Examples
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 thatp (fromJust (summaryMay (take (i+1) xs)))
isFalse
, orNothing
if there is no such index.j
is the least index such thatp (fromJust (summaryMay (take (j+1) xs)))
isTrue
, orNothing
if there is no such index.
Examples
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 thatp (fromJust (summaryMay (drop i xs)))
isTrue
, orNothing
if there is no such index.j
is the least index such thatp (fromJust (summaryMay (drop j xs)))
isFalse
, orNothing
if there is no such index
Examples
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
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.
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
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 -> 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).
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.
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 Just
s.
mapEither :: (Measured b, Measured c) => (a -> Either b c) -> MSeq a -> (MSeq b, MSeq c) Source #
\(O(n)\). Map over elements and split the Left
s and Right
s.
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 Just
s.
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 Left
s and Right
s.
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.
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
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.
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.
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) LT
s, followed by many EQ
s, followed by many GT
s.
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,
as the measure, since the Max
Word)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:
- Ralf Hinze and Ross Paterson, "Finger trees: a simple general-purpose data structure", Journal of Functional Programming 16(2), 197-217, 2006, https://doi.org/10.1017/S0956796805005769
One such use, priority queues, is implemented in this package and can be found in the module Data.Seqn.PQueue.