| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
RIO.Seq
Contents
Description
Seq. Import as:
import qualified RIO.Seq as Seq
- 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 :: Monad 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
- unstableSort :: Ord a => Seq a -> Seq a
- unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq a
- lookup :: Int -> Seq a -> Maybe a
- (!?) :: Seq a -> Int -> Maybe a
- index :: Seq a -> Int -> a
- adjust :: (a -> a) -> Int -> Seq a -> Seq a
- adjust' :: (a -> a) -> Int -> Seq a -> Seq a
- update :: Int -> a -> Seq a -> Seq a
- take :: Int -> Seq a -> Seq a
- drop :: Int -> Seq a -> Seq a
- 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
Documentation
General-purpose finite sequences.
Bundled Patterns
| pattern Empty :: forall a. Seq a | A pattern synonym matching an empty sequence. | 
| pattern (:<|) :: forall a. a -> Seq a -> Seq a infixr 5 | A pattern synonym viewing the front of a non-empty sequence. | 
| pattern (:|>) :: forall a. Seq a -> a -> Seq a infixl 5 | A pattern synonym viewing the rear of a non-empty sequence. | 
Instances
| Monad Seq | |
| Functor Seq | |
| Applicative Seq | |
| Foldable Seq | |
| Traversable Seq | |
| Eq1 Seq | |
| Ord1 Seq | |
| Read1 Seq | |
| Show1 Seq | |
| MonadZip Seq | |
| Alternative Seq | |
| MonadPlus Seq | |
| UnzipWith Seq | |
| IsList (Seq a) | |
| Eq a => Eq (Seq a) | |
| Data a => Data (Seq a) | |
| Ord a => Ord (Seq a) | |
| Read a => Read (Seq a) | |
| Show a => Show (Seq a) | |
| IsString (Seq Char) | |
| Semigroup (Seq a) | |
| Monoid (Seq a) | |
| NFData a => NFData (Seq a) | |
| type Item (Seq a) | |
Construction
(<|) :: a -> Seq a -> Seq a infixr 5 #
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 #
O(1). Add an element to the right end of a sequence. Mnemonic: a triangle with the single element at the pointy end.
fromFunction :: Int -> (Int -> a) -> Seq a #
O(n). Convert a given sequence length and a function representing that sequence into a sequence.
fromArray :: Ix i => Array i a -> Seq a #
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
replicateA :: Applicative f => Int -> f a -> f (Seq a) #
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) #
replicateM is a sequence counterpart of replicateM.
replicateM n x = sequence (replicate n x)
cycleTaking :: Int -> Seq a -> Seq a #
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 #
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 #
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
Additional functions for deconstructing sequences are available via the
 Foldable instance of Seq.
Queries
Views
View of the left end of a sequence.
View of the right end of a sequence.
Scans
Sublists
tails :: Seq a -> Seq (Seq a) #
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) #
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) #
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 #
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 #
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 #
O(i) where i is the prefix length.  dropWhileL p xstakeWhileL p xs
dropWhileR :: (a -> Bool) -> Seq a -> Seq a #
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) #
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) #
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) #
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) #
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 #
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 #
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 #
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 #
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 #
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 #
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 #
O(log(min(i,n-i))). A flipped, infix version of lookup.
Since: 0.5.8
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 #
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' :: (a -> a) -> Int -> Seq a -> Seq a #
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 #
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 #
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 #
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 #
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 #
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 elements.
elemIndexL :: Eq a => a -> Seq a -> Maybe Int #
elemIndexL finds the leftmost index of the specified element,
 if it is present, and otherwise Nothing.
elemIndicesL :: Eq a => a -> Seq a -> [Int] #
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 #
elemIndexR finds the rightmost index of the specified element,
 if it is present, and otherwise Nothing.
elemIndicesR :: Eq a => a -> Seq a -> [Int] #
elemIndicesR finds the indices of the specified element, from
 right to left (i.e. in descending order).
findIndexL :: (a -> Bool) -> Seq a -> Maybe Int #
findIndexL p xsp, if any exist.
findIndicesL :: (a -> Bool) -> Seq a -> [Int] #
findIndicesL pp,
 in ascending order.
findIndexR :: (a -> Bool) -> Seq a -> Maybe Int #
findIndexR p xsp, if any exist.
findIndicesR :: (a -> Bool) -> Seq a -> [Int] #
findIndicesR pp,
 in descending order.
Folds
General folds are available via the Foldable instance of Seq.
foldMapWithIndex :: Monoid m => (Int -> a -> m) -> Seq a -> m #
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 #
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 #
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 #
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) #
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 #
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
zip :: Seq a -> Seq b -> Seq (a, b) #
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.