containers-0.5.10.2: Assorted concrete container types

Copyright(c) Ross Paterson 2005
(c) Louis Wasserman 2009
(c) Bertram Felgenhauer David Feuer Ross Paterson and
Milan Straka 2014
LicenseBSD-style
Maintainer[email protected]
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Sequence.Internal

Contents

Description

WARNING

This module is considered internal.

The Package Versioning Policy does not apply.

This contents of this module may change in any way whatsoever and without any warning between minor versions of this package.

Authors importing this module are expected to track development closely.

Description

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

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.

Warning: The size of a Seq must not exceed maxBound::Int. Violation of this condition is not detected and if the size limit is exceeded, the behaviour of the sequence is undefined. This is unlikely to occur in most applications, but some care may be required when using ><, <*>, *>, or >>, particularly repeatedly and particularly in combination with replicate or fromFunction.

Synopsis

Documentation

newtype Elem a Source #

Constructors

Elem 

Fields

Instances

Functor Elem # 

Methods

fmap :: (a -> b) -> Elem a -> Elem b Source #

(<$) :: a -> Elem b -> Elem a Source #

Foldable Elem # 

Methods

fold :: Monoid m => Elem m -> m Source #

foldMap :: Monoid m => (a -> m) -> Elem a -> m Source #

foldr :: (a -> b -> b) -> b -> Elem a -> b Source #

foldr' :: (a -> b -> b) -> b -> Elem a -> b Source #

foldl :: (b -> a -> b) -> b -> Elem a -> b Source #

foldl' :: (b -> a -> b) -> b -> Elem a -> b Source #

foldr1 :: (a -> a -> a) -> Elem a -> a Source #

foldl1 :: (a -> a -> a) -> Elem a -> a Source #

toList :: Elem a -> [a] Source #

null :: Elem a -> Bool Source #

length :: Elem a -> Int Source #

elem :: Eq a => a -> Elem a -> Bool Source #

maximum :: Ord a => Elem a -> a Source #

minimum :: Ord a => Elem a -> a Source #

sum :: Num a => Elem a -> a Source #

product :: Num a => Elem a -> a Source #

Traversable Elem # 

Methods

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

sequenceA :: Applicative f => Elem (f a) -> f (Elem a) Source #

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

sequence :: Monad m => Elem (m a) -> m (Elem a) Source #

NFData a => NFData (Elem a) # 

Methods

rnf :: Elem a -> () Source #

MaybeForce (Elem a) # 

Methods

maybeRwhnf :: Elem a -> ()

Sized (Elem a) # 

Methods

size :: Elem a -> Int Source #

data FingerTree a Source #

Constructors

EmptyT 
Single a 
Deep !Int !(Digit a) (FingerTree (Node a)) !(Digit a) 

Instances

Functor FingerTree # 

Methods

fmap :: (a -> b) -> FingerTree a -> FingerTree b Source #

(<$) :: a -> FingerTree b -> FingerTree a Source #

Foldable FingerTree # 

Methods

fold :: Monoid m => FingerTree m -> m Source #

foldMap :: Monoid m => (a -> m) -> FingerTree a -> m Source #

foldr :: (a -> b -> b) -> b -> FingerTree a -> b Source #

foldr' :: (a -> b -> b) -> b -> FingerTree a -> b Source #

foldl :: (b -> a -> b) -> b -> FingerTree a -> b Source #

foldl' :: (b -> a -> b) -> b -> FingerTree a -> b Source #

foldr1 :: (a -> a -> a) -> FingerTree a -> a Source #

foldl1 :: (a -> a -> a) -> FingerTree a -> a Source #

toList :: FingerTree a -> [a] Source #

null :: FingerTree a -> Bool Source #

length :: FingerTree a -> Int Source #

elem :: Eq a => a -> FingerTree a -> Bool Source #

maximum :: Ord a => FingerTree a -> a Source #

minimum :: Ord a => FingerTree a -> a Source #

sum :: Num a => FingerTree a -> a Source #

product :: Num a => FingerTree a -> a Source #

Traversable FingerTree # 

Methods

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

sequenceA :: Applicative f => FingerTree (f a) -> f (FingerTree a) Source #

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

sequence :: Monad m => FingerTree (m a) -> m (FingerTree a) Source #

NFData a => NFData (FingerTree a) # 

Methods

rnf :: FingerTree a -> () Source #

Sized a => Sized (FingerTree a) # 

Methods

size :: FingerTree a -> Int Source #

data Node a Source #

Constructors

Node2 !Int a a 
Node3 !Int a a a 

Instances

Functor Node # 

Methods

fmap :: (a -> b) -> Node a -> Node b Source #

(<$) :: a -> Node b -> Node a Source #

Foldable Node # 

Methods

fold :: Monoid m => Node m -> m Source #

foldMap :: Monoid m => (a -> m) -> Node a -> m Source #

foldr :: (a -> b -> b) -> b -> Node a -> b Source #

foldr' :: (a -> b -> b) -> b -> Node a -> b Source #

foldl :: (b -> a -> b) -> b -> Node a -> b Source #

foldl' :: (b -> a -> b) -> b -> Node a -> b Source #

foldr1 :: (a -> a -> a) -> Node a -> a Source #

foldl1 :: (a -> a -> a) -> Node a -> a Source #

toList :: Node a -> [a] Source #

null :: Node a -> Bool Source #

length :: Node a -> Int Source #

elem :: Eq a => a -> Node a -> Bool Source #

maximum :: Ord a => Node a -> a Source #

minimum :: Ord a => Node a -> a Source #

sum :: Num a => Node a -> a Source #

product :: Num a => Node a -> a Source #

Traversable Node # 

Methods

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

sequenceA :: Applicative f => Node (f a) -> f (Node a) Source #

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

sequence :: Monad m => Node (m a) -> m (Node a) Source #

NFData a => NFData (Node a) # 

Methods

rnf :: Node a -> () Source #

MaybeForce (Node a) # 

Methods

maybeRwhnf :: Node a -> ()

Sized (Node a) # 

Methods

size :: Node a -> Int Source #

data Digit a Source #

Constructors

One a 
Two a a 
Three a a a 
Four a a a a 

Instances

Functor Digit # 

Methods

fmap :: (a -> b) -> Digit a -> Digit b Source #

(<$) :: a -> Digit b -> Digit a Source #

Foldable Digit # 

Methods

fold :: Monoid m => Digit m -> m Source #

foldMap :: Monoid m => (a -> m) -> Digit a -> m Source #

foldr :: (a -> b -> b) -> b -> Digit a -> b Source #

foldr' :: (a -> b -> b) -> b -> Digit a -> b Source #

foldl :: (b -> a -> b) -> b -> Digit a -> b Source #

foldl' :: (b -> a -> b) -> b -> Digit a -> b Source #

foldr1 :: (a -> a -> a) -> Digit a -> a Source #

foldl1 :: (a -> a -> a) -> Digit a -> a Source #

toList :: Digit a -> [a] Source #

null :: Digit a -> Bool Source #

length :: Digit a -> Int Source #

elem :: Eq a => a -> Digit a -> Bool Source #

maximum :: Ord a => Digit a -> a Source #

minimum :: Ord a => Digit a -> a Source #

sum :: Num a => Digit a -> a Source #

product :: Num a => Digit a -> a Source #

Traversable Digit # 

Methods

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

sequenceA :: Applicative f => Digit (f a) -> f (Digit a) Source #

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

sequence :: Monad m => Digit (m a) -> m (Digit a) Source #

NFData a => NFData (Digit a) # 

Methods

rnf :: Digit a -> () Source #

Sized a => Sized (Digit a) # 

Methods

size :: Digit a -> Int Source #

class Sized a where Source #

Minimal complete definition

size

Methods

size :: a -> Int Source #

Instances

Sized (Elem a) # 

Methods

size :: Elem a -> Int Source #

Sized (Node a) # 

Methods

size :: Node a -> Int Source #

Sized a => Sized (Digit a) # 

Methods

size :: Digit a -> Int Source #

Sized a => Sized (FingerTree a) # 

Methods

size :: FingerTree a -> Int Source #

class MaybeForce a Source #

Minimal complete definition

maybeRwhnf

Instances

MaybeForce (Elem a) # 

Methods

maybeRwhnf :: Elem a -> ()

MaybeForce (Node a) # 

Methods

maybeRwhnf :: Node a -> ()

newtype Seq a Source #

General-purpose finite sequences.

Constructors

Seq (FingerTree (Elem a)) 

Bundled Patterns

pattern Empty :: Seq a

A pattern synonym matching an empty sequence.

pattern (:<|) :: a -> Seq a -> Seq a infixr 5

A pattern synonym viewing the front of a non-empty sequence.

pattern (:|>) :: Seq a -> a -> Seq a infixl 5

A pattern synonym viewing the rear of a non-empty sequence.

Instances

Monad Seq # 

Methods

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

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

return :: a -> Seq a Source #

fail :: String -> Seq a Source #

Functor Seq # 

Methods

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

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

Applicative Seq # 

Methods

pure :: a -> Seq a Source #

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

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

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

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

Foldable Seq # 

Methods

fold :: Monoid m => Seq m -> m Source #

foldMap :: Monoid m => (a -> m) -> Seq a -> m Source #

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

foldr' :: (a -> b -> b) -> b -> Seq a -> b Source #

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

foldl' :: (b -> a -> b) -> b -> Seq a -> b Source #

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

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

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

null :: Seq a -> Bool Source #

length :: Seq a -> Int Source #

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

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

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

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

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

Traversable Seq # 

Methods

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

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

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

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

Eq1 Seq # 

Methods

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

Ord1 Seq # 

Methods

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

Read1 Seq # 

Methods

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

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

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

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

Show1 Seq # 

Methods

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

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

MonadZip Seq # 

Methods

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

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

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

Alternative Seq # 

Methods

empty :: Seq a Source #

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

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

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

MonadPlus Seq # 

Methods

mzero :: Seq a Source #

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

IsList (Seq a) # 

Associated Types

type Item (Seq a) :: * Source #

Methods

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

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

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

Eq a => Eq (Seq a) # 

Methods

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

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

Data a => Data (Seq a) # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) Source #

toConstr :: Seq a -> Constr Source #

dataTypeOf :: Seq a -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) Source #

Ord a => Ord (Seq a) # 

Methods

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

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

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

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

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

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

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

Read a => Read (Seq a) # 
Show a => Show (Seq a) # 

Methods

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

show :: Seq a -> String Source #

showList :: [Seq a] -> ShowS Source #

IsString (Seq Char) # 
Semigroup (Seq a) # 

Methods

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

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

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

Monoid (Seq a) # 

Methods

mempty :: Seq a Source #

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

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

NFData a => NFData (Seq a) # 

Methods

rnf :: Seq a -> () Source #

type Item (Seq a) # 
type Item (Seq a) = a

Construction

empty :: Seq a Source #

O(1). The empty sequence.

singleton :: a -> Seq a Source #

O(1). A singleton sequence.

(<|) :: a -> Seq a -> Seq a infixr 5 Source #

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 a infixl 5 Source #

O(1). Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.

(><) :: Seq a -> Seq a -> Seq a infixr 5 Source #

O(log(min(n1,n2))). Concatenate two sequences.

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

O(n). Create a sequence from a finite list of elements. There is a function toList in the opposite direction for all instances of the Foldable class, including Seq.

fromFunction :: Int -> (Int -> a) -> Seq a Source #

O(n). Convert a given sequence length and a function representing that sequence into a sequence.

fromArray :: Ix i => Array i a -> Seq a Source #

O(n). Create a sequence consisting of the elements of an Array. Note that the resulting sequence elements may be evaluated lazily (as on GHC), so you must force the entire structure to be sure that the original array can be garbage-collected.

Repetition

replicate :: Int -> a -> Seq a Source #

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 liftA2 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)

cycleTaking :: Int -> Seq a -> Seq a Source #

O(log(k)). cycleTaking k xs forms a sequence of length k by repeatedly concatenating xs with itself. xs may only be empty if k is 0.

cycleTaking k = fromList . take k . cycle . toList

Iterative construction

iterateN :: Int -> (a -> a) -> a -> Seq a Source #

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 a Source #

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.

unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a Source #

unfoldl f x is equivalent to reverse (unfoldr (fmap swap . f) x).

Deconstruction

Additional functions for deconstructing sequences are available via the Foldable instance of Seq.

Queries

null :: Seq a -> Bool Source #

O(1). Is this the empty sequence?

length :: Seq a -> Int Source #

O(1). The number of elements in the sequence.

Views

data ViewL a Source #

View of the left end of a sequence.

Constructors

EmptyL

empty sequence

a :< (Seq a) infixr 5

leftmost element and the rest of the sequence

Instances

Functor ViewL # 

Methods

fmap :: (a -> b) -> ViewL a -> ViewL b Source #

(<$) :: a -> ViewL b -> ViewL a Source #

Foldable ViewL # 

Methods

fold :: Monoid m => ViewL m -> m Source #

foldMap :: Monoid m => (a -> m) -> ViewL a -> m Source #

foldr :: (a -> b -> b) -> b -> ViewL a -> b Source #

foldr' :: (a -> b -> b) -> b -> ViewL a -> b Source #

foldl :: (b -> a -> b) -> b -> ViewL a -> b Source #

foldl' :: (b -> a -> b) -> b -> ViewL a -> b Source #

foldr1 :: (a -> a -> a) -> ViewL a -> a Source #

foldl1 :: (a -> a -> a) -> ViewL a -> a Source #

toList :: ViewL a -> [a] Source #

null :: ViewL a -> Bool Source #

length :: ViewL a -> Int Source #

elem :: Eq a => a -> ViewL a -> Bool Source #

maximum :: Ord a => ViewL a -> a Source #

minimum :: Ord a => ViewL a -> a Source #

sum :: Num a => ViewL a -> a Source #

product :: Num a => ViewL a -> a Source #

Traversable ViewL # 

Methods

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

sequenceA :: Applicative f => ViewL (f a) -> f (ViewL a) Source #

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

sequence :: Monad m => ViewL (m a) -> m (ViewL a) Source #

Eq a => Eq (ViewL a) # 

Methods

(==) :: ViewL a -> ViewL a -> Bool Source #

(/=) :: ViewL a -> ViewL a -> Bool Source #

Data a => Data (ViewL a) # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewL a -> c (ViewL a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewL a) Source #

toConstr :: ViewL a -> Constr Source #

dataTypeOf :: ViewL a -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ViewL a)) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewL a)) Source #

gmapT :: (forall b. Data b => b -> b) -> ViewL a -> ViewL a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ViewL a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewL a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) Source #

Ord a => Ord (ViewL a) # 

Methods

compare :: ViewL a -> ViewL a -> Ordering Source #

(<) :: ViewL a -> ViewL a -> Bool Source #

(<=) :: ViewL a -> ViewL a -> Bool Source #

(>) :: ViewL a -> ViewL a -> Bool Source #

(>=) :: ViewL a -> ViewL a -> Bool Source #

max :: ViewL a -> ViewL a -> ViewL a Source #

min :: ViewL a -> ViewL a -> ViewL a Source #

Read a => Read (ViewL a) # 
Show a => Show (ViewL a) # 
Generic (ViewL a) # 

Associated Types

type Rep (ViewL a) :: * -> * Source #

Methods

from :: ViewL a -> Rep (ViewL a) x Source #

to :: Rep (ViewL a) x -> ViewL a Source #

Generic1 * ViewL # 

Associated Types

type Rep1 ViewL (f :: ViewL -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 ViewL f a Source #

to1 :: Rep1 ViewL f a -> f a Source #

type Rep (ViewL a) # 
type Rep1 * ViewL # 

viewl :: Seq a -> ViewL a Source #

O(1). Analyse the left end of a sequence.

data ViewR a Source #

View of the right end of a sequence.

Constructors

EmptyR

empty sequence

(Seq a) :> a infixl 5

the sequence minus the rightmost element, and the rightmost element

Instances

Functor ViewR # 

Methods

fmap :: (a -> b) -> ViewR a -> ViewR b Source #

(<$) :: a -> ViewR b -> ViewR a Source #

Foldable ViewR # 

Methods

fold :: Monoid m => ViewR m -> m Source #

foldMap :: Monoid m => (a -> m) -> ViewR a -> m Source #

foldr :: (a -> b -> b) -> b -> ViewR a -> b Source #

foldr' :: (a -> b -> b) -> b -> ViewR a -> b Source #

foldl :: (b -> a -> b) -> b -> ViewR a -> b Source #

foldl' :: (b -> a -> b) -> b -> ViewR a -> b Source #

foldr1 :: (a -> a -> a) -> ViewR a -> a Source #

foldl1 :: (a -> a -> a) -> ViewR a -> a Source #

toList :: ViewR a -> [a] Source #

null :: ViewR a -> Bool Source #

length :: ViewR a -> Int Source #

elem :: Eq a => a -> ViewR a -> Bool Source #

maximum :: Ord a => ViewR a -> a Source #

minimum :: Ord a => ViewR a -> a Source #

sum :: Num a => ViewR a -> a Source #

product :: Num a => ViewR a -> a Source #

Traversable ViewR # 

Methods

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

sequenceA :: Applicative f => ViewR (f a) -> f (ViewR a) Source #

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

sequence :: Monad m => ViewR (m a) -> m (ViewR a) Source #

Eq a => Eq (ViewR a) # 

Methods

(==) :: ViewR a -> ViewR a -> Bool Source #

(/=) :: ViewR a -> ViewR a -> Bool Source #

Data a => Data (ViewR a) # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewR a -> c (ViewR a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewR a) Source #

toConstr :: ViewR a -> Constr Source #

dataTypeOf :: ViewR a -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ViewR a)) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewR a)) Source #

gmapT :: (forall b. Data b => b -> b) -> ViewR a -> ViewR a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ViewR a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewR a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) Source #

Ord a => Ord (ViewR a) # 

Methods

compare :: ViewR a -> ViewR a -> Ordering Source #

(<) :: ViewR a -> ViewR a -> Bool Source #

(<=) :: ViewR a -> ViewR a -> Bool Source #

(>) :: ViewR a -> ViewR a -> Bool Source #

(>=) :: ViewR a -> ViewR a -> Bool Source #

max :: ViewR a -> ViewR a -> ViewR a Source #

min :: ViewR a -> ViewR a -> ViewR a Source #

Read a => Read (ViewR a) # 
Show a => Show (ViewR a) # 
Generic (ViewR a) # 

Associated Types

type Rep (ViewR a) :: * -> * Source #

Methods

from :: ViewR a -> Rep (ViewR a) x Source #

to :: Rep (ViewR a) x -> ViewR a Source #

Generic1 * ViewR # 

Associated Types

type Rep1 ViewR (f :: ViewR -> *) :: k -> * Source #

Methods

from1 :: f a -> Rep1 ViewR f a Source #

to1 :: Rep1 ViewR f a -> f a Source #

type Rep (ViewR a) # 
type Rep1 * ViewR # 

viewr :: Seq a -> ViewR a Source #

O(1). Analyse the right end of a sequence.

Scans

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

scanl is similar to foldl, but returns a sequence of reduced values from the left:

scanl f z (fromList [x1, x2, ...]) = fromList [z, z `f` x1, (z `f` x1) `f` x2, ...]

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

scanl1 is a variant of scanl that has no starting value argument:

scanl1 f (fromList [x1, x2, ...]) = fromList [x1, x1 `f` x2, ...]

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

scanr is the right-to-left dual of scanl.

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

scanr1 is a variant of scanr that has no starting value argument.

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.

chunksOf :: Int -> Seq a -> Seq (Seq a) Source #

O(n). chunksOf n xs splits xs into chunks of size n>0. If n does not divide the length of xs evenly, then the last element of the result will be short.

Sequential searches

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

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 a Source #

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.

takeWhileR p xs is equivalent to reverse (takeWhileL p (reverse xs)).

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

O(i) where i is the prefix length. dropWhileL p xs returns the suffix remaining after takeWhileL p xs.

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

O(i) where i is the suffix length. dropWhileR p xs returns the prefix remaining after takeWhileR p xs.

dropWhileR p xs is equivalent to 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.

breakl p is equivalent to spanl (not . p).

breakr :: (a -> Bool) -> Seq a -> (Seq a, Seq a) Source #

breakr p is equivalent to spanr (not . p).

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 a Source #

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 a Source #

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 a Source #

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 a Source #

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 a Source #

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

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

O(log(min(i,n-i))). The element at the specified position, counting from 0. If the specified position is negative or at least the length of the sequence, lookup returns Nothing.

0 <= i < length xs ==> lookup i xs == Just (toList xs !! i)
i < 0 || i >= length xs ==> lookup i xs = Nothing

Unlike index, this can be used to retrieve an element without forcing it. For example, to insert the fifth element of a sequence xs into a Map m at key k, you could use

case lookup 5 xs of
  Nothing -> m
  Just x -> insert k x m

Since: 0.5.8

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

O(log(min(i,n-i))). A flipped, infix version of lookup.

Since: 0.5.8

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

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.

xs `index` i = toList xs !! i

Caution: index necessarily delays retrieving the requested element until the result is forced. It can therefore lead to a space leak if the result is stored, unforced, in another structure. To retrieve an element immediately without forcing it, use lookup or '(!?)'.

adjust :: (a -> a) -> Int -> Seq a -> Seq a Source #

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. adjust can lead to poor performance and even memory leaks, because it does not force the new value before installing it in the sequence. adjust' should usually be preferred.

adjust' :: forall a. (a -> a) -> Int -> Seq a -> Seq a Source #

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. The new value is forced before it is installed in the sequence.

adjust' f i xs =
 case xs !? i of
   Nothing -> xs
   Just x -> let !x' = f x
             in update i x' xs

Since: 0.5.8

update :: Int -> a -> Seq a -> Seq a Source #

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 a Source #

O(log(min(i,n-i))). The first i elements of a sequence. If i is negative, take i s yields the empty sequence. If the sequence contains fewer than i elements, the whole sequence is returned.

drop :: Int -> Seq a -> Seq a Source #

O(log(min(i,n-i))). Elements of a sequence after the first i. If i is negative, drop i s yields the whole sequence. If the sequence contains fewer than i elements, the empty sequence is returned.

insertAt :: Int -> a -> Seq a -> Seq a Source #

O(log(min(i,n-i))). insertAt i x xs inserts x into xs at the index i, shifting the rest of the sequence over.

insertAt 2 x (fromList [a,b,c,d]) = fromList [a,b,x,c,d]
insertAt 4 x (fromList [a,b,c,d]) = insertAt 10 x (fromList [a,b,c,d])
                                  = fromList [a,b,c,d,x]
insertAt i x xs = take i xs >< singleton x >< drop i xs

Since: 0.5.8

deleteAt :: Int -> Seq a -> Seq a Source #

O(log(min(i,n-i))). Delete the element of a sequence at a given index. Return the original sequence if the index is out of range.

deleteAt 2 [a,b,c,d] = [a,b,d]
deleteAt 4 [a,b,c,d] = deleteAt (-1) [a,b,c,d] = [a,b,c,d]

Since: 0.5.8

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

O(log(min(i,n-i))). Split a sequence at a given position. splitAt i s = (take i s, drop i s).

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 Int Source #

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 Int Source #

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 Int Source #

findIndexL p xs finds the index of the leftmost element that satisfies p, if any exist.

findIndicesL :: (a -> Bool) -> Seq a -> [Int] Source #

findIndicesL p finds all indices of elements that satisfy p, in ascending order.

findIndexR :: (a -> Bool) -> Seq a -> Maybe Int Source #

findIndexR p xs finds the index of the rightmost element that satisfies p, if any exist.

findIndicesR :: (a -> Bool) -> Seq a -> [Int] Source #

findIndicesR p finds all indices of elements that satisfy p, in descending order.

Folds

General folds are available via the Foldable instance of Seq.

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

O(n). A generalization of foldMap, foldMapWithIndex takes a folding function that also depends on the element's index, and applies it to every element in the sequence.

Since: 0.5.8

foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b Source #

foldlWithIndex is a version of foldl that also provides access to the index of each element.

foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #

foldrWithIndex is a version of foldr that also provides access to the index of each element.

Transformations

mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b Source #

O(n). 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.

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

traverseWithIndex is a version of traverse that also offers access to the index of each element.

Since: 0.5.8

reverse :: Seq a -> Seq a Source #

O(n). The reverse of a sequence.

intersperse :: a -> Seq a -> Seq a Source #

Intersperse an element between the elements of a sequence.

intersperse a empty = empty
intersperse a (singleton x) = singleton x
intersperse a (fromList [x,y]) = fromList [x,a,y]
intersperse a (fromList [x,y,z]) = fromList [x,a,y,a,z]

Since: 0.5.8

liftA2Seq :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

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.

zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c Source #

O(min(n1,n2)). zipWith generalizes zip by zipping with the function given as the first argument, instead of a tupling function. For example, zipWith (+) is applied to two sequences to take the sequence of corresponding sums.

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

O(min(n1,n2,n3)). zip3 takes three sequences and returns a sequence of triples, analogous to zip.

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

O(min(n1,n2,n3)). zipWith3 takes a function which combines three elements, as well as three sequences and returns a sequence of their point-wise combinations, analogous to zipWith.

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

O(min(n1,n2,n3,n4)). zip4 takes four sequences and returns a sequence of quadruples, analogous to zip.

zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e Source #

O(min(n1,n2,n3,n4)). zipWith4 takes a function which combines four elements, as well as four sequences and returns a sequence of their point-wise combinations, analogous to zipWith.