Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Seqn.Seq
Description
Finite sequences
A value of type Seq a
is a sequence with elements of type a
.
A Seq
is
- Spine-strict, hence finite.
Seq
cannot represent infinite sequences. - Value-strict. It is guaranteed that if a
Seq
is in weak head normal form (WHNF), every element of theSeq
is also in WHNF.
It is recommended to import this module qualified to avoid name clashes.
import Data.Seqn.Seq (Seq) import qualified Data.Seqn.Seq as Seq
Warning
The length of a Seq
must not exceed (maxBound `div` 3) :: Int
. If this
length is exceeded, the behavior of a Seq
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.
Implementation
Seq
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 Seq a
- empty :: Seq a
- singleton :: a -> Seq a
- fromList :: [a] -> Seq a
- fromRevList :: [a] -> Seq a
- replicate :: Int -> a -> Seq a
- replicateA :: Applicative f => Int -> f a -> f (Seq a)
- generate :: Int -> (Int -> a) -> Seq a
- generateA :: Applicative f => Int -> (Int -> f a) -> f (Seq a)
- unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a
- unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a
- unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> m (Seq a)
- unfoldlM :: Monad m => (b -> m (Maybe (b, a))) -> b -> m (Seq a)
- concatMap :: Foldable f => (a -> Seq b) -> f a -> Seq b
- toRevList :: Seq a -> [a]
- lookup :: Int -> Seq a -> Maybe a
- index :: Int -> Seq a -> a
- (!?) :: Seq a -> Int -> Maybe a
- (!) :: Seq a -> Int -> a
- update :: Int -> a -> Seq a -> Seq a
- adjust :: (a -> a) -> Int -> Seq a -> Seq a
- insertAt :: Int -> a -> Seq a -> Seq a
- deleteAt :: Int -> Seq a -> Seq a
- cons :: a -> Seq a -> Seq a
- snoc :: Seq a -> a -> Seq a
- uncons :: Seq a -> Maybe (a, Seq a)
- unsnoc :: Seq a -> Maybe (Seq a, a)
- take :: Int -> Seq a -> Seq a
- drop :: Int -> Seq a -> Seq a
- slice :: (Int, Int) -> Seq a -> Seq a
- splitAt :: Int -> Seq a -> (Seq a, Seq a)
- takeEnd :: Int -> Seq a -> Seq a
- dropEnd :: Int -> Seq a -> Seq a
- splitAtEnd :: Int -> Seq a -> (Seq a, Seq a)
- tails :: Seq a -> Seq (Seq a)
- inits :: Seq a -> Seq (Seq a)
- chunksOf :: Int -> Seq a -> Seq (Seq a)
- filter :: (a -> Bool) -> Seq a -> Seq a
- catMaybes :: Seq (Maybe a) -> Seq a
- mapMaybe :: (a -> Maybe b) -> Seq a -> Seq b
- mapEither :: (a -> Either b c) -> Seq a -> (Seq b, Seq c)
- filterA :: Applicative f => (a -> f Bool) -> Seq a -> f (Seq a)
- mapMaybeA :: Applicative f => (a -> f (Maybe b)) -> Seq a -> f (Seq b)
- mapEitherA :: Applicative f => (a -> f (Either b c)) -> Seq a -> f (Seq b, Seq c)
- takeWhile :: (a -> Bool) -> Seq a -> Seq a
- dropWhile :: (a -> Bool) -> Seq a -> Seq a
- span :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- break :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- takeWhileEnd :: (a -> Bool) -> Seq a -> Seq a
- dropWhileEnd :: (a -> Bool) -> Seq a -> Seq a
- spanEnd :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- breakEnd :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
- reverse :: Seq a -> Seq a
- intersperse :: a -> Seq a -> Seq a
- scanl :: (b -> a -> b) -> b -> Seq a -> Seq b
- scanr :: (a -> b -> b) -> b -> Seq a -> Seq b
- sort :: Ord a => Seq a -> Seq a
- sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a
- findEnd :: (a -> Bool) -> Seq a -> Maybe a
- findIndex :: (a -> Bool) -> Seq a -> Maybe Int
- findIndexEnd :: (a -> Bool) -> Seq a -> Maybe Int
- infixIndices :: Eq a => Seq a -> Seq a -> [Int]
- binarySearchFind :: (a -> Ordering) -> Seq a -> Maybe a
- isPrefixOf :: Eq a => Seq a -> Seq a -> Bool
- isSuffixOf :: Eq a => Seq a -> Seq a -> Bool
- isInfixOf :: Eq a => Seq a -> Seq a -> Bool
- isSubsequenceOf :: Eq a => Seq a -> Seq a -> Bool
- zip :: Seq a -> Seq b -> Seq (a, b)
- zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c)
- zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
- zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
- zipWithM :: Monad m => (a -> b -> m c) -> Seq a -> Seq b -> m (Seq c)
- zipWith3M :: Monad m => (a -> b -> c -> m d) -> Seq a -> Seq b -> Seq c -> m (Seq d)
- unzip :: Seq (a, b) -> (Seq a, Seq b)
- unzip3 :: Seq (a, b, c) -> (Seq a, Seq b, Seq c)
- unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
- unzipWith3 :: (a -> (b, c, d)) -> Seq a -> (Seq b, Seq c, Seq d)
Seq
A sequence with elements of type a
.
Instances
MonadFail Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
MonadFix Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
MonadZip Seq Source # | |
Foldable Seq Source # |
Folds are \(O(n)\). |
Defined in Data.Seqn.Internal.Seq Methods fold :: Monoid m => Seq m -> m # foldMap :: Monoid m => (a -> m) -> Seq a -> m # foldMap' :: Monoid m => (a -> m) -> Seq a -> m # foldr :: (a -> b -> b) -> b -> Seq a -> b # foldr' :: (a -> b -> b) -> b -> Seq a -> b # foldl :: (b -> a -> b) -> b -> Seq a -> b # foldl' :: (b -> a -> b) -> b -> Seq a -> b # foldr1 :: (a -> a -> a) -> Seq a -> a # foldl1 :: (a -> a -> a) -> Seq a -> a # elem :: Eq a => a -> Seq a -> Bool # maximum :: Ord a => Seq a -> a # | |
Eq1 Seq Source # | |
Ord1 Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
Read1 Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
Show1 Seq Source # | |
Traversable Seq Source # | |
Alternative Seq Source # | |
Applicative Seq Source # |
|
Functor Seq Source # |
|
Monad Seq Source # | |
MonadPlus Seq Source # | |
NFData1 Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
FoldableWithIndex Int Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
FunctorWithIndex Int Seq Source # | |
TraversableWithIndex Int Seq Source # | |
Defined in Data.Seqn.Internal.Seq | |
a ~ Char => IsString (Seq a) Source # | |
Defined in Data.Seqn.Internal.Seq Methods fromString :: String -> Seq a # | |
Monoid (Seq a) Source # |
|
Semigroup (Seq a) Source # |
|
IsList (Seq a) Source # | |
Read a => Read (Seq a) Source # | |
Show a => Show (Seq a) Source # | |
NFData a => NFData (Seq a) Source # | |
Defined in Data.Seqn.Internal.Seq | |
Eq a => Eq (Seq a) Source # | |
Ord a => Ord (Seq a) Source # | Lexicographical ordering |
type Item (Seq a) Source # | |
Defined in Data.Seqn.Internal.Seq |
Construct
fromList :: [a] -> Seq a Source #
\(O(n)\). Create a Seq
from a list.
Examples
>>>
fromList [8,1,19,11,5,12,12]
[8,1,19,11,5,12,12]
fromRevList :: [a] -> Seq a Source #
\(O(n)\). Create a Seq
from a reversed list.
Examples
>>>
fromRevList "!olleH"
"Hello!"
replicate :: Int -> a -> Seq a Source #
\(O(\log n)\). A sequence with a repeated element.
If the length is negative, empty
is returned.
Examples
>>>
replicate 3 "ha"
["ha","ha","ha"]
replicateA :: Applicative f => Int -> f a -> f (Seq a) Source #
\(O(n)\). Generate a sequence from a length and an applicative action.
If the length is negative, empty
is returned.
Examples
>>>
import System.Random (randomIO)
>>>
import Data.Word (Word8)
>>>
replicateA 5 (randomIO :: IO Word8)
[26,134,30,58,221]
generate :: Int -> (Int -> a) -> Seq a Source #
\(O(n)\). Generate a sequence from a length and a generator.
If the length is negative, empty
is returned.
Examples
>>>
generate 4 (10*)
[0,10,20,30]
generateA :: Applicative f => Int -> (Int -> f a) -> f (Seq a) Source #
\(O(n)\). Generate a sequence from a length and an applicative generator.
If the length is negative, empty
is returned.
unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a Source #
\(O(n)\). Unfold a sequence from left to right.
Examples
>>>
let f (i,a,b) = if i >= 10 then Nothing else Just (a, (i+1, b, a+b))
>>>
unfoldr f (0,0,1)
[0,1,1,2,3,5,8,13,21,34]
unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a Source #
\(O(n)\). Unfold a sequence from right to left.
Examples
>>>
let f i = if i <= 0 then Nothing else Just (i `div` 2, i)
>>>
unfoldl f 1024
[1,2,4,8,16,32,64,128,256,512,1024]
unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> m (Seq a) Source #
\(O(n)\). Unfold a sequence monadically from left to right.
unfoldlM :: Monad m => (b -> m (Maybe (b, a))) -> b -> m (Seq a) Source #
\(O(n)\). Unfold a sequence monadically from right to left.
concatMap :: Foldable f => (a -> Seq b) -> f a -> Seq b Source #
\(O \left(\sum_i \log n_i \right)\).
Map over a Foldable
and concatenate the results.
Examples
>>>
concatMap (uncurry replicate) [(1,'H'),(1,'e'),(2,'l'),(1,'o')]
"Hello"
Convert
toRevList :: Seq a -> [a] Source #
\(O(n)\). Convert to a list in reverse.
To convert to a list without reversing, use
Data.Foldable.
.toList
Examples
>>>
toRevList (fromList "!olleH")
"Hello!"
Index
lookup :: Int -> Seq a -> Maybe a Source #
\(O(\log n)\). Look up the element at an index.
Examples
>>>
lookup 3 (fromList "haskell")
Just 'k'>>>
lookup (-1) (singleton 7)
Nothing
index :: Int -> Seq a -> a Source #
\(O(\log n)\). Look up the element at an index. Calls error
if the index
is out of bounds.
Examples
>>>
index 3 (fromList "haskell")
'k'>>>
index (-1) (singleton 7)
*** Exception: ...
(!) :: Seq a -> Int -> a Source #
\(O(\log n)\). Infix version of index
. Calls error
if the index is out
of bounds.
update :: Int -> a -> Seq a -> Seq a Source #
\(O(\log n)\). Update an element at an index. If the index is out of bounds, the sequence is returned unchanged.
Examples
>>>
update 3 'b' (fromList "bird")
"birb">>>
update 3 True (singleton False)
[False]
adjust :: (a -> a) -> Int -> Seq a -> Seq a Source #
\(O(\log n)\). Adjust the element at an index. If the index is out of bounds the sequence is returned unchanged.
Examples
>>>
adjust Data.List.reverse 1 (fromList ["Hello", "ereht"])
["Hello","there"]>>>
adjust (*100) (-1) (singleton 7)
[7]
insertAt :: Int -> a -> Seq a -> Seq 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.
Examples
>>>
insertAt 1 'a' (fromList "ct")
"cat">>>
insertAt (-10) 0 (fromList [5,6,7])
[0,5,6,7]>>>
insertAt 10 0 (fromList [5,6,7])
[5,6,7,0]
deleteAt :: Int -> Seq a -> Seq a Source #
\(O(\log n)\). Delete an element at an index. If the index is out of bounds, the sequence is returned unchanged.
Examples
>>>
deleteAt 2 (fromList "cart")
"cat">>>
deleteAt 10 (fromList [5,6,7])
[5,6,7]
Slice
cons :: a -> Seq a -> Seq a Source #
\(O(\log n)\). Append a value to the beginning of a sequence.
Examples
>>>
cons 1 (fromList [2,3])
[1,2,3]
snoc :: Seq a -> a -> Seq a Source #
\(O(\log n)\). Append a value to the end of a sequence.
Examples
>>>
snoc (fromList [1,2]) 3
[1,2,3]
uncons :: Seq a -> Maybe (a, Seq a) Source #
\(O(\log n)\). The head and tail of a sequence.
Examples
>>>
uncons (fromList [1,2,3])
Just (1,[2,3])>>>
uncons empty
Nothing
unsnoc :: Seq a -> Maybe (Seq a, a) Source #
\(O(\log n)\). The init and last of a sequence.
Examples
>>>
unsnoc (fromList [1,2,3])
Just ([1,2],3)>>>
unsnoc empty
Nothing
take :: Int -> Seq a -> Seq a Source #
\(O(\log n)\). Take a number of elements from the beginning of a sequence.
Examples
>>>
take 3 (fromList "haskell")
"has">>>
take (-1) (fromList [1,2,3])
[]>>>
take 10 (fromList [1,2,3])
[1,2,3]
drop :: Int -> Seq a -> Seq a Source #
\(O(\log n)\). Drop a number of elements from the beginning of a sequence.
Examples
>>>
drop 3 (fromList "haskell")
"kell">>>
drop (-1) (fromList [1,2,3])
[1,2,3]>>>
drop 10 (fromList [1,2,3])
[]
slice :: (Int, Int) -> Seq a -> Seq a Source #
\(O(\log n)\). The slice of a sequence between two indices (inclusive).
Examples
>>>
slice (1,3) (fromList "haskell")
"ask">>>
slice (-10,2) (fromList [1,2,3,4,5])
[1,2,3]>>>
slice (2,1) (fromList [1,2,3,4,5])
[]
takeEnd :: Int -> Seq a -> Seq a Source #
\(O(\log n)\). Take a number of elements from the end of a sequence.
dropEnd :: Int -> Seq a -> Seq a Source #
\(O(\log n)\). Drop a number of elements from the end of a sequence.
tails :: Seq a -> Seq (Seq a) Source #
\(O(n \log n)\). All suffixes of a sequence, longest first.
Examples
>>>
tails (fromList [1,2,3])
[[1,2,3],[2,3],[3],[]]
inits :: Seq a -> Seq (Seq a) Source #
\(O(n \log n)\). All prefixes of a sequence, shortest first.
Examples
>>>
inits (fromList [1,2,3])
[[],[1],[1,2],[1,2,3]]
chunksOf :: Int -> Seq a -> Seq (Seq a) Source #
\(O \left(\frac{n}{c} \log c \right)\). Split a sequence into chunks of the
given length c
. If c <= 0
, empty
is returned.
Examples
>>>
chunksOf 3 (fromList [1..10])
[[1,2,3],[4,5,6],[7,8,9],[10]]>>>
chunksOf 10 (fromList "hello")
["hello"]>>>
chunksOf (-1) (singleton 7)
[]
Filter
filter :: (a -> Bool) -> Seq a -> Seq a Source #
\(O(n)\). Keep elements that satisfy a predicate.
Examples
>>>
filter even (fromList [1..10])
[2,4,6,8,10]
catMaybes :: Seq (Maybe a) -> Seq a Source #
\(O(n)\). Keep the Just
s in a sequence.
Examples
>>>
catMaybes (fromList [Just 1, Nothing, Nothing, Just 10, Just 100])
[1,10,100]
mapMaybe :: (a -> Maybe b) -> Seq a -> Seq b Source #
\(O(n)\). Map over elements and collect the Just
s.
mapEither :: (a -> Either b c) -> Seq a -> (Seq b, Seq c) Source #
\(O(n)\). Map over elements and split the Left
s and Right
s.
Examples
>>>
mapEither (\x -> if odd x then Left x else Right x) (fromList [1..10])
([1,3,5,7,9],[2,4,6,8,10])
filterA :: Applicative f => (a -> f Bool) -> Seq a -> f (Seq a) Source #
\(O(n)\). Keep elements that satisfy an applicative predicate.
mapMaybeA :: Applicative f => (a -> f (Maybe b)) -> Seq a -> f (Seq b) Source #
\(O(n)\). Traverse over elements and collect the Just
s.
mapEitherA :: Applicative f => (a -> f (Either b c)) -> Seq a -> f (Seq b, Seq c) Source #
\(O(n)\). Traverse over elements and split the Left
s and Right
s.
takeWhile :: (a -> Bool) -> Seq a -> Seq a Source #
\(O(i + \log n)\). The longest prefix of elements that satisfy a predicate. \(i\) is the length of the prefix.
Examples
>>>
takeWhile even (fromList [2,4,6,1,3,2,4])
[2,4,6]
dropWhile :: (a -> Bool) -> Seq a -> Seq 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.
Examples
>>>
dropWhile even (fromList [2,4,6,1,3,2,4])
[1,3,2,4]
break :: (a -> Bool) -> Seq a -> (Seq a, Seq 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)
Examples
>>>
break odd (fromList [2,4,6,1,3,2,4])
([2,4,6],[1,3,2,4])
takeWhileEnd :: (a -> Bool) -> Seq a -> Seq a Source #
\(O(i + \log n)\). The longest suffix of elements that satisfy a predicate. \(i\) is the length of the suffix.
dropWhileEnd :: (a -> Bool) -> Seq a -> Seq 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 :: (a -> Bool) -> Seq a -> (Seq a, Seq 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 :: (a -> Bool) -> Seq a -> (Seq a, Seq 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
reverse :: Seq a -> Seq a Source #
\(O(n)\). Reverse a sequence.
Examples
>>>
reverse (fromList [1,2,3,4,5])
[5,4,3,2,1]
intersperse :: a -> Seq a -> Seq a Source #
\(O(n)\). Intersperse an element between the elements of a sequence.
Examples
>>>
intersperse '.' (fromList "HELLO")
"H.E.L.L.O"
scanl :: (b -> a -> b) -> b -> Seq a -> Seq b Source #
\(O(n)\). Like foldl'
but keeps all intermediate values.
Examples
>>>
scanl (+) 0 (fromList [1..5])
[0,1,3,6,10,15]
scanr :: (a -> b -> b) -> b -> Seq a -> Seq b Source #
\(O(n)\). Like foldr'
but keeps all intermediate values.
Examples
>>>
scanr (+) 0 (fromList [1..5])
[15,14,12,9,5,0]
sort :: Ord a => Seq a -> Seq a Source #
\(O(n \log n)\). Sort a sequence. The sort is stable.
Examples
>>>
sort (fromList [4,2,3,5,1])
[1,2,3,4,5]
sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a Source #
\(O(n \log n)\). Sort a sequence using a comparison function. The sort is stable.
Examples
>>>
import Data.Ord (Down, comparing)
>>>
sortBy (comparing Down) (fromList [4,2,3,5,1])
[5,4,3,2,1]
Search and test
findEnd :: (a -> Bool) -> Seq a -> Maybe a Source #
\(O(n)\). The last element satisfying a predicate.
To get the first element, use Data.Foldable.
.find
findIndex :: (a -> Bool) -> Seq a -> Maybe Int Source #
\(O(n)\). The index of the first element satisfying a predicate.
Examples
>>>
findIndex even (fromList [1..5])
Just 1>>>
findIndex (<0) (fromList [1..5])
Nothing
findIndexEnd :: (a -> Bool) -> Seq a -> Maybe Int Source #
\(O(n)\). The index of the last element satisfying a predicate.
infixIndices :: Eq a => Seq a -> Seq a -> [Int] Source #
\(O(n_1 + n_2)\). Indices in the second sequence where the first sequence begins as a substring. Includes overlapping occurences.
Examples
>>>
infixIndices (fromList "ana") (fromList "banana")
[1,3]>>>
infixIndices (fromList [0]) (fromList [1,2,3])
[]>>>
infixIndices (fromList "") (fromList "abc")
[0,1,2,3]
binarySearchFind :: (a -> Ordering) -> Seq 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.
Examples
>>>
binarySearchFind (`compare` 8) (fromList [2,4..10])
Just 8>>>
binarySearchFind (`compare` 3) (fromList [2,4..10])
Nothing
isPrefixOf :: Eq a => Seq a -> Seq a -> Bool Source #
\(O(\min(n_1,n_2))\). Whether the first sequence is a prefix of the second.
Examples
>>>
fromList "has" `isPrefixOf` fromList "haskell"
True>>>
fromList "ask" `isPrefixOf` fromList "haskell"
False
isSuffixOf :: Eq a => Seq a -> Seq a -> Bool Source #
\(O(\min(n_1,n_2))\). Whether the first sequence is a suffix of the second.
Examples
>>>
fromList "ell" `isSuffixOf` fromList "haskell"
True>>>
fromList "ask" `isSuffixOf` fromList "haskell"
False
isInfixOf :: Eq a => Seq a -> Seq a -> Bool Source #
\(O(n_1 + n_2)\). Whether the first sequence is a substring of the second.
Examples
>>>
fromList "meow" `isInfixOf` fromList "homeowner"
True>>>
fromList [2,4] `isInfixOf` fromList [2,3,4]
False
isSubsequenceOf :: Eq a => Seq a -> Seq a -> Bool Source #
\(O(n_1 + n_2)\). Whether the first sequence is a subsequence of the second.
Examples
>>>
fromList [2,4] `isSubsequenceOf` [2,3,4]
True>>>
fromList "tab" `isSubsequenceOf` fromList "bat"
False
Zip and unzip
zip :: Seq a -> Seq b -> Seq (a, b) Source #
\(O(\min(n_1,n_2))\). Zip two sequences. The result is as long as the shorter sequence.
zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c) Source #
\(O(\min(n_1,n_2,n_3))\). Zip three sequences. The result is as long as the shortest sequence.
zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #
\(O(\min(n_1,n_2))\). Zip two sequences with a function. The result is as long as the shorter sequence.
Examples
>>>
zipWith (+) (fromList [1,2,3]) (fromList [1,1,1,1,1])
[2,3,4]
zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq 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 :: Monad m => (a -> b -> m c) -> Seq a -> Seq b -> m (Seq c) Source #
\(O(\min(n_1,n_2))\). Zip two sequences with a monadic function. The result is as long as the shorter sequence.
zipWith3M :: Monad m => (a -> b -> c -> m d) -> Seq a -> Seq b -> Seq c -> m (Seq d) Source #
\(O(\min(n_1,n_2,n_3))\). Zip three sequences with a monadic function. The result is as long as the shortest sequence.