Portability | portable |
---|---|
Stability | experimental |
Maintainer | libraries@haskell.org |
Safe Haskell | Trustworthy |
General purpose finite sequences. Apart from being finite and having strict operations, sequences also differ from lists in supporting a wider variety of operations efficiently.
An amortized running time is given for each operation, with n referring to the length of the sequence and i being the integral index used by some operations. These bounds hold even in a persistent (shared) setting.
The implementation uses 2-3 finger trees annotated with sizes, as described in section 4.2 of
- Ralf Hinze and Ross Paterson, "Finger trees: a simple general-purpose data structure", Journal of Functional Programming 16:2 (2006) pp 197-217. http://www.soi.city.ac.uk/~ross/papers/FingerTree.html
Note: Many of these operations have the same names as similar
operations on lists in the Prelude. The ambiguity may be resolved
using either qualification or the hiding
clause.
- data Seq a
- empty :: Seq a
- singleton :: a -> Seq a
- (<|) :: a -> Seq a -> Seq a
- (|>) :: Seq a -> a -> Seq a
- (><) :: Seq a -> Seq a -> Seq a
- fromList :: [a] -> Seq a
- replicate :: Int -> a -> Seq a
- replicateA :: Applicative f => Int -> f a -> f (Seq a)
- replicateM :: Monad m => Int -> m a -> m (Seq a)
- iterateN :: Int -> (a -> a) -> a -> Seq a
- unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a
- unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a
- null :: Seq a -> Bool
- length :: Seq a -> Int
- data ViewL a
- viewl :: Seq a -> ViewL a
- data ViewR a
- viewr :: Seq a -> ViewR a
- scanl :: (a -> b -> a) -> a -> Seq b -> Seq a
- scanl1 :: (a -> a -> a) -> Seq a -> Seq a
- scanr :: (a -> b -> b) -> b -> Seq a -> Seq b
- scanr1 :: (a -> a -> a) -> Seq a -> Seq a
- tails :: Seq a -> Seq (Seq a)
- inits :: Seq a -> Seq (Seq a)
- takeWhileL :: (a -> Bool) -> Seq a -> Seq a
- takeWhileR :: (a -> Bool) -> Seq a -> Seq a
- dropWhileL :: (a -> Bool) -> Seq a -> Seq a
- dropWhileR :: (a -> Bool) -> Seq a -> Seq a
- spanl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- spanr :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- breakl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- breakr :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- filter :: (a -> Bool) -> Seq a -> Seq a
- sort :: Ord a => Seq a -> Seq a
- sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a
- unstableSort :: Ord a => Seq a -> Seq a
- unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq a
- index :: Seq a -> Int -> a
- adjust :: (a -> a) -> Int -> Seq a -> Seq a
- update :: Int -> a -> Seq a -> Seq a
- take :: Int -> Seq a -> Seq a
- drop :: Int -> Seq a -> Seq a
- splitAt :: Int -> Seq a -> (Seq a, Seq a)
- elemIndexL :: Eq a => a -> Seq a -> Maybe Int
- elemIndicesL :: Eq a => a -> Seq a -> [Int]
- elemIndexR :: Eq a => a -> Seq a -> Maybe Int
- elemIndicesR :: Eq a => a -> Seq a -> [Int]
- findIndexL :: (a -> Bool) -> Seq a -> Maybe Int
- findIndicesL :: (a -> Bool) -> Seq a -> [Int]
- findIndexR :: (a -> Bool) -> Seq a -> Maybe Int
- findIndicesR :: (a -> Bool) -> Seq a -> [Int]
- foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b
- foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b
- mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b
- reverse :: Seq a -> Seq a
- zip :: Seq a -> Seq b -> Seq (a, b)
- zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
- zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c)
- zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
- zip4 :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d)
- zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e
Documentation
General-purpose finite sequences.
Construction
(<|) :: a -> Seq a -> Seq aSource
O(1). Add an element to the left end of a sequence. Mnemonic: a triangle with the single element at the pointy end.
(|>) :: Seq a -> a -> Seq aSource
O(1). Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.
Repetition
replicate :: Int -> a -> Seq aSource
O(log n). replicate n x
is a sequence consisting of n
copies of x
.
replicateA :: Applicative f => Int -> f a -> f (Seq a)Source
replicateA
is an Applicative
version of replicate
, and makes
O(log n) calls to <*>
and pure
.
replicateA n x = sequenceA (replicate n x)
replicateM :: Monad m => Int -> m a -> m (Seq a)Source
replicateM
is a sequence counterpart of replicateM
.
replicateM n x = sequence (replicate n x)
Iterative construction
iterateN :: Int -> (a -> a) -> a -> Seq aSource
O(n). Constructs a sequence by repeated application of a function to a seed value.
iterateN n f x = fromList (Prelude.take n (Prelude.iterate f x))
unfoldr :: (b -> Maybe (a, b)) -> b -> Seq aSource
Builds a sequence from a seed value. Takes time linear in the number of generated elements. WARNING: If the number of generated elements is infinite, this method will not terminate.
Deconstruction
Queries
Views
View of the left end of a sequence.
View of the right end of a sequence.
Scans
Sublists
tails :: Seq a -> Seq (Seq a)Source
O(n). Returns a sequence of all suffixes of this sequence, longest first. For example,
tails (fromList "abc") = fromList [fromList "abc", fromList "bc", fromList "c", fromList ""]
Evaluating the ith suffix takes O(log(min(i, n-i))), but evaluating every suffix in the sequence takes O(n) due to sharing.
inits :: Seq a -> Seq (Seq a)Source
O(n). Returns a sequence of all prefixes of this sequence, shortest first. For example,
inits (fromList "abc") = fromList [fromList "", fromList "a", fromList "ab", fromList "abc"]
Evaluating the ith prefix takes O(log(min(i, n-i))), but evaluating every prefix in the sequence takes O(n) due to sharing.
Sequential searches
takeWhileL :: (a -> Bool) -> Seq a -> Seq aSource
O(i) where i is the prefix length. takeWhileL
, applied
to a predicate p
and a sequence xs
, returns the longest prefix
(possibly empty) of xs
of elements that satisfy p
.
takeWhileR :: (a -> Bool) -> Seq a -> Seq aSource
O(i) where i is the suffix length. takeWhileR
, applied
to a predicate p
and a sequence xs
, returns the longest suffix
(possibly empty) of xs
of elements that satisfy p
.
is equivalent to takeWhileR
p xs
.
reverse
(takeWhileL
p (reverse
xs))
dropWhileL :: (a -> Bool) -> Seq a -> Seq aSource
O(i) where i is the prefix length.
returns
the suffix remaining after dropWhileL
p xs
.
takeWhileL
p xs
dropWhileR :: (a -> Bool) -> Seq a -> Seq aSource
O(i) where i is the suffix length.
returns
the prefix remaining after dropWhileR
p xs
.
takeWhileR
p xs
is equivalent to dropWhileR
p xs
.
reverse
(dropWhileL
p (reverse
xs))
spanl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source
O(i) where i is the prefix length. spanl
, applied to
a predicate p
and a sequence xs
, returns a pair whose first
element is the longest prefix (possibly empty) of xs
of elements that
satisfy p
and the second element is the remainder of the sequence.
spanr :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source
O(i) where i is the suffix length. spanr
, applied to a
predicate p
and a sequence xs
, returns a pair whose first element
is the longest suffix (possibly empty) of xs
of elements that
satisfy p
and the second element is the remainder of the sequence.
breakl :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source
O(i) where i is the breakpoint index. breakl
, applied to a
predicate p
and a sequence xs
, returns a pair whose first element
is the longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and the second element is the remainder of
the sequence.
partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a)Source
O(n). The partition
function takes a predicate p
and a
sequence xs
and returns sequences of those elements which do and
do not satisfy the predicate.
filter :: (a -> Bool) -> Seq a -> Seq aSource
O(n). The filter
function takes a predicate p
and a sequence
xs
and returns a sequence of those elements which satisfy the
predicate.
Sorting
sort :: Ord a => Seq a -> Seq aSource
O(n log n). sort
sorts the specified Seq
by the natural
ordering of its elements. The sort is stable.
If stability is not required, unstableSort
can be considerably
faster, and in particular uses less memory.
sortBy :: (a -> a -> Ordering) -> Seq a -> Seq aSource
O(n log n). sortBy
sorts the specified Seq
according to the
specified comparator. The sort is stable.
If stability is not required, unstableSortBy
can be considerably
faster, and in particular uses less memory.
unstableSort :: Ord a => Seq a -> Seq aSource
O(n log n). unstableSort
sorts the specified Seq
by
the natural ordering of its elements, but the sort is not stable.
This algorithm is frequently faster and uses less memory than sort
,
and performs extremely well -- frequently twice as fast as sort
--
when the sequence is already nearly sorted.
unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq aSource
O(n log n). A generalization of unstableSort
, unstableSortBy
takes an arbitrary comparator and sorts the specified sequence.
The sort is not stable. This algorithm is frequently faster and
uses less memory than sortBy
, and performs extremely well --
frequently twice as fast as sortBy
-- when the sequence is already
nearly sorted.
Indexing
index :: Seq a -> Int -> aSource
O(log(min(i,n-i))). The element at the specified position,
counting from 0. The argument should thus be a non-negative
integer less than the size of the sequence.
If the position is out of range, index
fails with an error.
adjust :: (a -> a) -> Int -> Seq a -> Seq aSource
O(log(min(i,n-i))). Update the element at the specified position. If the position is out of range, the original sequence is returned.
update :: Int -> a -> Seq a -> Seq aSource
O(log(min(i,n-i))). Replace the element at the specified position. If the position is out of range, the original sequence is returned.
take :: Int -> Seq a -> Seq aSource
O(log(min(i,n-i))). The first i
elements of a sequence.
If i
is negative,
yields the empty sequence.
If the sequence contains fewer than take
i si
elements, the whole sequence
is returned.
drop :: Int -> Seq a -> Seq aSource
O(log(min(i,n-i))). Elements of a sequence after the first i
.
If i
is negative,
yields the whole sequence.
If the sequence contains fewer than drop
i si
elements, the empty sequence
is returned.
Indexing with predicates
These functions perform sequential searches from the left or right ends of the sequence, returning indices of matching elements.
elemIndexL :: Eq a => a -> Seq a -> Maybe IntSource
elemIndexL
finds the leftmost index of the specified element,
if it is present, and otherwise Nothing
.
elemIndicesL :: Eq a => a -> Seq a -> [Int]Source
elemIndicesL
finds the indices of the specified element, from
left to right (i.e. in ascending order).
elemIndexR :: Eq a => a -> Seq a -> Maybe IntSource
elemIndexR
finds the rightmost index of the specified element,
if it is present, and otherwise Nothing
.
elemIndicesR :: Eq a => a -> Seq a -> [Int]Source
elemIndicesR
finds the indices of the specified element, from
right to left (i.e. in descending order).
findIndexL :: (a -> Bool) -> Seq a -> Maybe IntSource
finds the index of the leftmost element that
satisfies findIndexL
p xsp
, if any exist.
findIndicesL :: (a -> Bool) -> Seq a -> [Int]Source
finds all indices of elements that satisfy findIndicesL
pp
,
in ascending order.
findIndexR :: (a -> Bool) -> Seq a -> Maybe IntSource
finds the index of the rightmost element that
satisfies findIndexR
p xsp
, if any exist.
findIndicesR :: (a -> Bool) -> Seq a -> [Int]Source
finds all indices of elements that satisfy findIndicesR
pp
,
in descending order.
Folds
foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> bSource
foldlWithIndex
is a version of foldl
that also provides access
to the index of each element.
foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> bSource
foldrWithIndex
is a version of foldr
that also provides access
to the index of each element.
Transformations
mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq bSource
A generalization of fmap
, mapWithIndex
takes a mapping function
that also depends on the element's index, and applies it to every
element in the sequence.
Zips
zip :: Seq a -> Seq b -> Seq (a, b)Source
O(min(n1,n2)). zip
takes two sequences and returns a sequence
of corresponding pairs. If one input is short, excess elements are
discarded from the right end of the longer sequence.