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

Data.Seqn.Internal.Seq

Description

This is an internal module. You probably don't need to import this. Use Data.Seqn.Seq instead.

WARNING

Definitions in this module allow violating invariants that would otherwise be guaranteed by Data.Seqn.Seq. Use at your own risk!

Synopsis

Seq

data Seq a Source #

A sequence with elements of type a.

Constructors

Tree !a !(Tree a) 
Empty 

Instances

Instances details
MonadFail Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

fail :: String -> Seq a #

MonadFix Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

MonadZip Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

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

Foldable Seq Source #
length
\(O(1)\).

Folds are \(O(n)\).

Instance details

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 #

toList :: Seq a -> [a] #

null :: Seq a -> Bool #

length :: Seq a -> Int #

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

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

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

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

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

Eq1 Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

Ord1 Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

Read1 Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

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

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

Show1 Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

Traversable Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

traverse :: Applicative f => (a -> f b) -> Seq a -> f (Seq b) #

sequenceA :: Applicative f => Seq (f a) -> f (Seq a) #

mapM :: Monad m => (a -> m b) -> Seq a -> m (Seq b) #

sequence :: Monad m => Seq (m a) -> m (Seq a) #

Alternative Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

empty :: Seq a #

(<|>) :: Seq a -> Seq a -> Seq a #

some :: Seq a -> Seq [a] #

many :: Seq a -> Seq [a] #

Applicative Seq Source #
liftA2
\(O(n_1 n_2)\).
(<*)
\(O(n_1 \log n_2)\).
(*>)
\(O(\log n_1)\).
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

pure :: a -> Seq a #

(<*>) :: Seq (a -> b) -> Seq a -> Seq b #

liftA2 :: (a -> b -> c) -> Seq a -> Seq b -> Seq c #

(*>) :: Seq a -> Seq b -> Seq b #

(<*) :: Seq a -> Seq b -> Seq a #

Functor Seq Source #
fmap
\(O(n)\).
(<$)
\(O(\log n)\).
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

Monad Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

(>>=) :: Seq a -> (a -> Seq b) -> Seq b #

(>>) :: Seq a -> Seq b -> Seq b #

return :: a -> Seq a #

MonadPlus Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

mzero :: Seq a #

mplus :: Seq a -> Seq a -> Seq a #

NFData1 Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

FoldableWithIndex Int Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

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

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

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

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

FunctorWithIndex Int Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

TraversableWithIndex Int Seq Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

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

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

Defined in Data.Seqn.Internal.Seq

Methods

fromString :: String -> Seq a #

Monoid (Seq a) Source #
mempty
The empty sequence.
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

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

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

Defined in Data.Seqn.Internal.Seq

Methods

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

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

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

IsList (Seq a) Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Associated Types

type Item (Seq a) #

Methods

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

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

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

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

Defined in Data.Seqn.Internal.Seq

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

Defined in Data.Seqn.Internal.Seq

Methods

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

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

NFData a => NFData (Seq a) Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

Methods

rnf :: Seq a -> () #

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

Defined in Data.Seqn.Internal.Seq

Methods

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

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

Ord a => Ord (Seq a) Source #

Lexicographical ordering

Instance details

Defined in Data.Seqn.Internal.Seq

Methods

compare :: Seq a -> Seq a -> Ordering #

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

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

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

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

max :: Seq a -> Seq a -> Seq a #

min :: Seq a -> Seq a -> Seq a #

type Item (Seq a) Source # 
Instance details

Defined in Data.Seqn.Internal.Seq

type Item (Seq a) = a

Construct

empty :: Seq a Source #

The empty sequence.

singleton :: a -> Seq a Source #

A singleton sequence.

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

\(O(n)\). Create a Seq from a list.

Examples

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> toRevList (fromList "!olleH")
"Hello!"

Index

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

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

Examples

Expand
>>> 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

Expand
>>> index 3 (fromList "haskell")
'k'
>>> index (-1) (singleton 7)
*** Exception: ...

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

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

(!) :: 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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])
[]

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

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

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

Examples

Expand
>>> splitAt 3 (fromList "haskell")
("has","kell")
>>> splitAt (-1) (fromList [1,2,3])
([],[1,2,3])
>>> splitAt 10 (fromList [1,2,3])
([1,2,3],[])

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.

splitAtEnd :: Int -> Seq a -> (Seq a, Seq a) Source #

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

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

tails :: Seq a -> Seq (Seq a) Source #

\(O(n \log n)\). All suffixes of a sequence, longest first.

Examples

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> filter even (fromList [1..10])
[2,4,6,8,10]

catMaybes :: Seq (Maybe a) -> Seq a Source #

\(O(n)\). Keep the Justs in a sequence.

Examples

Expand
>>> 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 Justs.

mapEither :: (a -> Either b c) -> Seq a -> (Seq b, Seq c) Source #

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

Examples

Expand
>>> 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 Justs.

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

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

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

Expand
>>> 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

Expand
>>> dropWhile even (fromList [2,4,6,1,3,2,4])
[1,3,2,4]

span :: (a -> Bool) -> Seq a -> (Seq a, Seq 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)

Examples

Expand
>>> span even (fromList [2,4,6,1,3,2,4])
([2,4,6],[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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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) LTs, followed by many EQs, followed by many GTs.

Examples

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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

Expand
>>> 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.

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

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

unzip3 :: Seq (a, b, c) -> (Seq a, Seq b, Seq c) Source #

\(O(n)\). Unzip a sequence of triples.

unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) Source #

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

Examples

Expand
>>> unzipWith (\x -> (x-1, x*2)) (fromList [1..5])
([0,1,2,3,4],[2,4,6,8,10])

unzipWith3 :: (a -> (b, c, d)) -> Seq a -> (Seq b, Seq c, Seq d) Source #

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

Internal

Testing