| Copyright | (c) Ross Paterson 2005 (c) Louis Wasserman 2009 (c) Bertram Felgenhauer David Feuer Ross Paterson and Milan Straka 2014 | 
|---|---|
| License | BSD-style | 
| Maintainer | libraries@haskell.org | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Strict.Sequence.Autogen
Description
Finite sequences
The Seq aa.
Sequences generally behave very much like lists.
- The class instances for sequences are all based very closely on those for lists.
- Many functions in this module have the same names as functions in
 the Prelude or in Data.List. In almost all cases, these functions
 behave analogously. For example, filterfilters a sequence in exactly the same way thatPrelude.filters a list. The only major exception is thefilterlookupfunction, which is based on the function by that name in Data.IntMap rather than the one in Prelude.
There are two major differences between sequences and lists:
- Sequences support a wider variety of efficient operations than do lists. Notably, they offer - Constant-time access to both the front and the rear with
<|,|>,viewl,viewr. For recent GHC versions, this can be done more conveniently using the bidirectional patternsEmpty,:<|, and:|>. See the detailed explanation in the "Pattern synonyms" section.
- Logarithmic-time concatenation with ><
- Logarithmic-time splitting with splitAt,takeanddrop
- Logarithmic-time access to any element with
lookup,!?,index,insertAt,deleteAt,adjust, andupdate
 
- Constant-time access to both the front and the rear with
Note that sequences are typically slower than lists when using only operations for which they have the same big-(O) complexity: sequences make rather mediocre stacks!
- Whereas lists can be either finite or infinite, sequences are always finite. As a result, a sequence is strict in its length. Ignoring efficiency, you can imagine that - Seqis defined- data Seq a = Empty | a :<| !(Seq a) - This means that many operations on sequences are stricter than those on lists. For example, - (1 : undefined) !! 0 = 1 - but - (1 :<| undefined) - `index`0 = undefined
Sequences may also be compared to immutable arrays or vectors. Like these structures, sequences support fast indexing, although not as fast. But editing an immutable array or vector, or combining it with another, generally requires copying the entire structure; sequences generally avoid that, copying only the portion that has changed.
Detailed performance information
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.
Despite sequences being structurally strict from a semantic standpoint, they are in fact implemented using laziness internally. As a result, many operations can be performed incrementally, producing their results as they are demanded. This greatly improves performance in some cases. These functions include
- The Functormethodsfmapand<$, along withmapWithIndex
- The Applicativemethods<*>,*>, and<*
- The zips: zipWith,zip, etc.
- inits,- tails
- fromFunction,- replicate,- intersperse, and- cycleTaking
- reverse
- chunksOf
Note that the Monad method, >>=, is not particularly lazy. It will
 take time proportional to the sum of the logarithms of the individual
 result sequences to produce anything whatsoever.
Several functions take special advantage of sharing to produce results using much less time and memory than one might expect. These are documented individually for functions, but also include certain class methods:
<$ and *> each take time and space proportional
 to the logarithm of the size of their result.
<* takes time and space proportional to the product of the length
 of its first argument and the logarithm of the length of its second
 argument.
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.
Implementation
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.
Synopsis
- data Seq a where
- 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
- fromFunction :: Int -> (Int -> a) -> Seq a
- fromArray :: Ix i => Array i a -> Seq a
- replicate :: Int -> a -> Seq a
- replicateA :: Applicative f => Int -> f a -> f (Seq a)
- replicateM :: Applicative m => Int -> m a -> m (Seq a)
- cycleTaking :: Int -> Seq a -> 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)
- chunksOf :: Int -> 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
- sortOn :: Ord b => (a -> b) -> Seq a -> Seq a
- unstableSort :: Ord a => Seq a -> Seq a
- unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq a
- unstableSortOn :: Ord b => (a -> b) -> Seq a -> Seq a
- lookup :: Int -> Seq a -> Maybe a
- (!?) :: Seq a -> Int -> Maybe a
- index :: Seq a -> Int -> a
- adjust :: forall a. (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
- insertAt :: Int -> a -> Seq a -> Seq a
- deleteAt :: 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]
- foldMapWithIndex :: Monoid m => (Int -> a -> m) -> Seq a -> m
- 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
- traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b)
- reverse :: Seq a -> Seq a
- intersperse :: a -> 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
- unzip :: Seq (a, b) -> (Seq a, Seq b)
- unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
Finite sequences
General-purpose finite sequences.
Bundled Patterns
| pattern Empty :: Seq a | A bidirectional pattern synonym matching an empty sequence. Since: 0.5.8 | 
| pattern (:<|) :: a -> Seq a -> Seq a infixr 5 | A bidirectional pattern synonym viewing the front of a non-empty sequence. Since: 0.5.8 | 
| pattern (:|>) :: Seq a -> a -> Seq a infixl 5 | A bidirectional pattern synonym viewing the rear of a non-empty sequence. Since: 0.5.8 | 
Instances
| MonadFix Seq Source # | Since: 0.5.11 | 
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| MonadZip Seq Source # | 
 
 | 
| Foldable Seq Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal 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 # | Since: 0.5.9 | 
| Ord1 Seq Source # | Since: 0.5.9 | 
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| Read1 Seq Source # | Since: 0.5.9 | 
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| Show1 Seq Source # | Since: 0.5.9 | 
| Traversable Seq Source # | |
| Alternative Seq Source # | Since: 0.5.4 | 
| Applicative Seq Source # | Since: 0.5.4 | 
| Functor Seq Source # | |
| Monad Seq Source # | |
| MonadPlus Seq Source # | |
| FoldableWithIndex Int Seq Source # | |
| Defined in Data.Strict.Sequence.Internal | |
| FunctorWithIndex Int Seq Source # | The position in the  | 
| TraversableWithIndex Int Seq Source # | |
| Defined in Data.Strict.Sequence.Internal | |
| Lift a => Lift (Seq a :: TYPE LiftedRep) Source # | @since FIXME | 
| Data a => Data (Seq a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Seq a -> c (Seq a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Seq a) # dataTypeOf :: Seq a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Seq a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Seq a)) # gmapT :: (forall b. Data b => b -> b) -> Seq a -> Seq a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Seq a -> r # gmapQ :: (forall d. Data d => d -> u) -> Seq a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Seq a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Seq a -> m (Seq a) # | |
| a ~ Char => IsString (Seq a) Source # | Since: 0.5.7 | 
| Defined in Data.Strict.Sequence.Autogen.Internal Methods fromString :: String -> Seq a # | |
| Monoid (Seq a) Source # | |
| Semigroup (Seq a) Source # | Since: 0.5.7 | 
| IsList (Seq a) Source # | |
| Read a => Read (Seq a) Source # | |
| Show a => Show (Seq a) Source # | |
| Binary e => Binary (Seq e) Source # | |
| NFData a => NFData (Seq a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| Eq a => Eq (Seq a) Source # | |
| Ord a => Ord (Seq a) Source # | |
| Strict (Seq k) (Seq k) Source # | |
| type Item (Seq a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal | |
Pattern synonyms
Much like lists can be constructed and matched using the
: and [] constructors, sequences can be constructed and
matched using the Empty, :<|, and :|> pattern synonyms.
Note
These patterns are only available with GHC version 8.0 or later,
and version 8.2 works better with them. When writing for such recent
versions of GHC, the patterns can be used in place of empty,
<|, |>, viewl, and viewr.
Pattern synonym examples
Import the patterns:
import Data.Strict.Sequence.Autogen (Seq (..))
Look at the first three elements of a sequence
getFirst3 :: Seq a -> Maybe (a,a,a) getFirst3 (x1 :<| x2 :<| x3 :<| _xs) = Just (x1,x2,x3) getFirst3 _ = Nothing
> getFirst3 (fromList[1,2,3,4]) = Just (1,2,3) > getFirst3 (fromList[1,2]) = Nothing
Move the last two elements from the end of the first list onto the beginning of the second one.
shift2Right :: Seq a -> Seq a -> (Seq a, Seq a) shift2Right Empty ys = (Empty, ys) shift2Right (Empty :|> x) ys = (Empty, x :<| ys) shift2Right (xs :|> x1 :|> x2) ys = (xs, x1 :<| x2 :<| ys)
> shift2Right (fromList[]) (fromList[10]) = (fromList[],fromList[10]) > shift2Right (fromList[9]) (fromList[10]) = (fromList[],fromList[9,10]) > shift2Right (fromList[8,9]) (fromList[10]) = (fromList[],fromList[8,9,10]) > shift2Right (fromList[7,8,9]) (fromList[10]) = (fromList[7],fromList[8,9,10])
Construction
(<|) :: 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(n_1,n_2))) \). Concatenate two sequences.
fromFunction :: Int -> (Int -> a) -> Seq a Source #
\( O(n) \). Convert a given sequence length and a function representing that sequence into a sequence.
Since: 0.5.6.2
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.
Since: 0.5.6.2
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 :: Applicative m => Int -> m a -> m (Seq a) Source #
replicateM is a sequence counterpart of replicateM.
replicateM n x = sequence (replicate n x)
For base >= 4.8.0 and containers >= 0.5.11, replicateM
 is a synonym for replicateA.
cycleTaking :: Int -> Seq a -> Seq a Source #
\(O(\log k)\). cycleTaking k xsk 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.
Deconstruction
Queries
Views
View of the left end of a sequence.
Instances
| Foldable ViewL Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal Methods fold :: Monoid m => ViewL m -> m # foldMap :: Monoid m => (a -> m) -> ViewL a -> m # foldMap' :: Monoid m => (a -> m) -> ViewL a -> m # foldr :: (a -> b -> b) -> b -> ViewL a -> b # foldr' :: (a -> b -> b) -> b -> ViewL a -> b # foldl :: (b -> a -> b) -> b -> ViewL a -> b # foldl' :: (b -> a -> b) -> b -> ViewL a -> b # foldr1 :: (a -> a -> a) -> ViewL a -> a # foldl1 :: (a -> a -> a) -> ViewL a -> a # elem :: Eq a => a -> ViewL a -> Bool # maximum :: Ord a => ViewL a -> a # minimum :: Ord a => ViewL a -> a # | |
| Traversable ViewL Source # | |
| Functor ViewL Source # | |
| Lift a => Lift (ViewL a :: Type) Source # | @since FIXME | 
| Data a => Data (ViewL a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewL a -> c (ViewL a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewL a) # toConstr :: ViewL a -> Constr # dataTypeOf :: ViewL a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ViewL a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewL a)) # gmapT :: (forall b. Data b => b -> b) -> ViewL a -> ViewL a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewL a -> r # gmapQ :: (forall d. Data d => d -> u) -> ViewL a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewL a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewL a -> m (ViewL a) # | |
| Generic (ViewL a) Source # | |
| Read a => Read (ViewL a) Source # | |
| Show a => Show (ViewL a) Source # | |
| Eq a => Eq (ViewL a) Source # | |
| Ord a => Ord (ViewL a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| Generic1 ViewL Source # | |
| type Rep (ViewL a) Source # | Since: 0.5.8 | 
| Defined in Data.Strict.Sequence.Autogen.Internal type Rep (ViewL a) = D1 ('MetaData "ViewL" "Data.Strict.Sequence.Autogen.Internal" "strict-containers-0.2-wNLN6SH1Ig3uC6wtMh5Gp" 'False) (C1 ('MetaCons "EmptyL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":<" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a)))) | |
| type Rep1 ViewL Source # | Since: 0.5.8 | 
| Defined in Data.Strict.Sequence.Autogen.Internal type Rep1 ViewL = D1 ('MetaData "ViewL" "Data.Strict.Sequence.Autogen.Internal" "strict-containers-0.2-wNLN6SH1Ig3uC6wtMh5Gp" 'False) (C1 ('MetaCons "EmptyL" 'PrefixI 'False) (U1 :: TYPE LiftedRep -> Type) :+: C1 ('MetaCons ":<" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Seq))) | |
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
| Foldable ViewR Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal Methods fold :: Monoid m => ViewR m -> m # foldMap :: Monoid m => (a -> m) -> ViewR a -> m # foldMap' :: Monoid m => (a -> m) -> ViewR a -> m # foldr :: (a -> b -> b) -> b -> ViewR a -> b # foldr' :: (a -> b -> b) -> b -> ViewR a -> b # foldl :: (b -> a -> b) -> b -> ViewR a -> b # foldl' :: (b -> a -> b) -> b -> ViewR a -> b # foldr1 :: (a -> a -> a) -> ViewR a -> a # foldl1 :: (a -> a -> a) -> ViewR a -> a # elem :: Eq a => a -> ViewR a -> Bool # maximum :: Ord a => ViewR a -> a # minimum :: Ord a => ViewR a -> a # | |
| Traversable ViewR Source # | |
| Functor ViewR Source # | |
| Generic1 ViewR Source # | |
| Lift a => Lift (ViewR a :: Type) Source # | @since FIXME | 
| Data a => Data (ViewR a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewR a -> c (ViewR a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ViewR a) # toConstr :: ViewR a -> Constr # dataTypeOf :: ViewR a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (ViewR a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ViewR a)) # gmapT :: (forall b. Data b => b -> b) -> ViewR a -> ViewR a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewR a -> r # gmapQ :: (forall d. Data d => d -> u) -> ViewR a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewR a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewR a -> m (ViewR a) # | |
| Generic (ViewR a) Source # | |
| Read a => Read (ViewR a) Source # | |
| Show a => Show (ViewR a) Source # | |
| Eq a => Eq (ViewR a) Source # | |
| Ord a => Ord (ViewR a) Source # | |
| Defined in Data.Strict.Sequence.Autogen.Internal | |
| type Rep1 ViewR Source # | Since: 0.5.8 | 
| Defined in Data.Strict.Sequence.Autogen.Internal type Rep1 ViewR = D1 ('MetaData "ViewR" "Data.Strict.Sequence.Autogen.Internal" "strict-containers-0.2-wNLN6SH1Ig3uC6wtMh5Gp" 'False) (C1 ('MetaCons "EmptyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":>" ('InfixI 'LeftAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Seq) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
| type Rep (ViewR a) Source # | Since: 0.5.8 | 
| Defined in Data.Strict.Sequence.Autogen.Internal type Rep (ViewR a) = D1 ('MetaData "ViewR" "Data.Strict.Sequence.Autogen.Internal" "strict-containers-0.2-wNLN6SH1Ig3uC6wtMh5Gp" 'False) (C1 ('MetaCons "EmptyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":>" ('InfixI 'LeftAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) | |
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 \( i \)th 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 \( i \)th 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 \Bigl(\bigl(\frac{n}{c}\bigr) \log c\Bigr)\). chunksOf c xs splits xs into chunks of size c>0.
 If c does not divide the length of xs evenly, then the last element
 of the result will be short.
Side note: the given performance bound is missing some messy terms that only really affect edge cases. Performance degrades smoothly from \( O(1) \) (for \( c = n \)) to \( O(n) \) (for \( c = 1 \)). The true bound is more like \( O \Bigl( \bigl(\frac{n}{c} - 1\bigr) (\log (c + 1)) + 1 \Bigr) \)
Since: 0.5.8
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 xsreverse (takeWhileL p (reverse xs))
dropWhileL :: (a -> Bool) -> Seq a -> Seq a Source #
\( O(i) \) where \( i \) is the prefix length.  dropWhileL p xstakeWhileL p xs
dropWhileR :: (a -> Bool) -> Seq a -> Seq a Source #
\( O(i) \) where \( i \) is the suffix length.  dropWhileR p xstakeWhileR p xs
dropWhileR p xsreverse (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 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 slightly faster.
Since: 0.3.0
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 slightly faster.
Since: 0.3.0
sortOn :: Ord b => (a -> b) -> Seq a -> Seq a Source #
\( O(n \log n) \). sortOn sorts the specified Seq by comparing
 the results of a key function applied to each element. sortOn fsortBy (compare `on` f)f once for each element in the
 input list. This is called the decorate-sort-undecorate paradigm, or
 Schwartzian transform.
An example of using sortOn might be to sort a Seq of strings
 according to their length:
sortOn length (fromList ["alligator", "monkey", "zebra"]) == fromList ["zebra", "monkey", "alligator"]
If, instead, sortBy had been used, length would be evaluated on
 every comparison, giving \( O(n \log n) \) evaluations, rather than
 \( O(n) \).
If f is very cheap (for example a record selector, or fst),
 sortBy (compare `on` f)sortOn f
Since: 0.5.11
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.
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.
Since: 0.3.0
unstableSortOn :: Ord b => (a -> b) -> Seq a -> Seq a Source #
\( O(n \log n) \). unstableSortOn sorts the specified Seq by
 comparing the results of a key function applied to each element.
 unstableSortOn funstableSortBy (compare `on` f)f once for each
 element in the input list. This is called the
 decorate-sort-undecorate paradigm, or Schwartzian transform.
An example of using unstableSortOn might be to sort a Seq of strings
 according to their length:
unstableSortOn length (fromList ["alligator", "monkey", "zebra"]) == fromList ["zebra", "monkey", "alligator"]
If, instead, unstableSortBy had been used, length would be evaluated on
 every comparison, giving \( O(n \log n) \) evaluations, rather than
 \( O(n) \).
If f is very cheap (for example a record selector, or fst),
 unstableSortBy (compare `on` f)unstableSortOn f
Since: 0.5.11
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 :: 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 si 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 si elements, the empty sequence
 is returned.
insertAt :: Int -> a -> Seq a -> Seq a Source #
\( O(\log(\min(i,n-i))) \). insertAt i x xsx 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
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 xsp, if any exist.
findIndicesL :: (a -> Bool) -> Seq a -> [Int] Source #
findIndicesL pp,
 in ascending order.
findIndexR :: (a -> Bool) -> Seq a -> Maybe Int Source #
findIndexR p xsp, if any exist.
findIndicesR :: (a -> Bool) -> Seq a -> [Int] Source #
findIndicesR pp,
 in descending order.
Folds
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 #
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
intersperse :: a -> Seq a -> Seq a Source #
\( O(n) \). 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
Zips and unzip
zip :: Seq a -> Seq b -> Seq (a, b) Source #
\( O(\min(n_1,n_2)) \).  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.
unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) Source #
\( O(n) \). Unzip a sequence using a function to divide elements.
unzipWith f xs ==unzip(fmapf xs)
Efficiency note:
unzipWith produces its two results in lockstep. If you calculate
  unzipWith f xs  and fully force either of the results, then the
 entire structure of the other one will be built as well. This
 behavior allows the garbage collector to collect each calculated
 pair component as soon as it dies, without having to wait for its mate
 to die. If you do not need this behavior, you may be better off simply
 calculating the sequence of pairs and using fmap to extract each
 component sequence.
Since: 0.5.11