1{-# LANGUAGE CPP #-}
2#ifdef __HADDOCK_VERSION__
3{-# OPTIONS_GHC -Wno-unused-imports #-}
4#endif
5
6#include "containers.h"
7
8-----------------------------------------------------------------------------
9-- |
10-- Module      :  Data.Sequence
11-- Copyright   :  (c) Ross Paterson 2005
12--                (c) Louis Wasserman 2009
13--                (c) Bertram Felgenhauer, David Feuer, Ross Paterson, and
14--                    Milan Straka 2014
15-- License     :  BSD-style
16-- Maintainer  :  libraries@haskell.org
17-- Portability :  portable
18--
19-- = Finite sequences
20--
21-- The @'Seq' a@ type represents a finite sequence of values of
22-- type @a@.
23--
24-- Sequences generally behave very much like lists.
25--
26-- * The class instances for sequences are all based very closely on those for
27-- lists.
28--
29-- * Many functions in this module have the same names as functions in
30-- the "Prelude" or in "Data.List". In almost all cases, these functions
31-- behave analogously. For example, 'filter' filters a sequence in exactly the
32-- same way that @"Prelude".'Prelude.filter'@ filters a list. The only major
33-- exception is the 'lookup' function, which is based on the function by
34-- that name in "Data.IntMap" rather than the one in "Prelude".
35--
36-- There are two major differences between sequences and lists:
37--
38-- * Sequences support a wider variety of efficient operations than
39-- do lists. Notably, they offer
40--
41--     * Constant-time access to both the front and the rear with
42--     '<|', '|>', 'viewl', 'viewr'. For recent GHC versions, this can
43--     be done more conveniently using the bidirectional patterns 'Empty',
44--     ':<|', and ':|>'. See the detailed explanation in the \"Pattern synonyms\"
45--     section.
46--     * Logarithmic-time concatenation with '><'
47--     * Logarithmic-time splitting with 'splitAt', 'take' and 'drop'
48--     * Logarithmic-time access to any element with
49--     'lookup', '!?', 'index', 'insertAt', 'deleteAt', 'adjust'', and 'update'
50--
51--   Note that sequences are typically /slower/ than lists when using only
52--   operations for which they have the same big-\(O\) complexity: sequences
53--   make rather mediocre stacks!
54--
55-- * Whereas lists can be either finite or infinite, sequences are
56-- always finite. As a result, a sequence is strict in its
57-- length. Ignoring efficiency, you can imagine that 'Seq' is defined
58--
59--     @ data Seq a = Empty | a :<| !(Seq a) @
60--
61--     This means that many operations on sequences are stricter than
62--     those on lists. For example,
63--
64--     @ (1 : undefined) !! 0 = 1 @
65--
66--     but
67--
68--     @ (1 :<| undefined) `index` 0 = undefined @
69--
70-- Sequences may also be compared to immutable
71-- [arrays](https://hackage.haskell.org/package/array)
72-- or [vectors](https://hackage.haskell.org/package/vector).
73-- Like these structures, sequences support fast indexing,
74-- although not as fast. But editing an immutable array or vector,
75-- or combining it with another, generally requires copying the
76-- entire structure; sequences generally avoid that, copying only
77-- the portion that has changed.
78--
79-- == Detailed performance information
80--
81-- An amortized running time is given for each operation, with /n/ referring
82-- to the length of the sequence and /i/ being the integral index used by
83-- some operations. These bounds hold even in a persistent (shared) setting.
84--
85-- Despite sequences being structurally strict from a semantic standpoint,
86-- they are in fact implemented using laziness internally. As a result,
87-- many operations can be performed /incrementally/, producing their results
88-- as they are demanded. This greatly improves performance in some cases. These
89-- functions include
90--
91-- * The 'Functor' methods 'fmap' and '<$', along with 'mapWithIndex'
92-- * The 'Applicative' methods '<*>', '*>', and '<*'
93-- * The zips: 'zipWith', 'zip', etc.
94-- * 'heads' and 'tails'
95-- * 'fromFunction', 'replicate', 'intersperse', and 'cycleTaking'
96-- * 'reverse'
97-- * 'chunksOf'
98--
99-- Note that the 'Monad' method, '>>=', is not particularly lazy. It will
100-- take time proportional to the sum of the logarithms of the individual
101-- result sequences to produce anything whatsoever.
102--
103-- Several functions take special advantage of sharing to produce
104-- results using much less time and memory than one might expect. These
105-- are documented individually for functions, but also include the
106-- methods '<$' and '*>', each of which take time and space proportional
107-- to the logarithm of the size of the result.
108--
109-- == Warning
110--
111-- The size of a 'Seq' must not exceed @maxBound::Int@. Violation
112-- of this condition is not detected and if the size limit is exceeded, the
113-- behaviour of the sequence is undefined. This is unlikely to occur in most
114-- applications, but some care may be required when using '><', '<*>', '*>', or
115-- '>>', particularly repeatedly and particularly in combination with
116-- 'replicate' or 'fromFunction'.
117--
118-- == Implementation
119--
120-- The implementation uses 2-3 finger trees annotated with sizes,
121-- as described in section 4.2 of
122--
123--    * Ralf Hinze and Ross Paterson,
124--      [\"Finger trees: a simple general-purpose data structure\"]
125--      (http://staff.city.ac.uk/~ross/papers/FingerTree.html),
126--      /Journal of Functional Programming/ 16:2 (2006) pp 197-217.
127--
128-----------------------------------------------------------------------------
129
130
131module Data.Sequence (
132    -- * Finite sequences
133#if defined(DEFINE_PATTERN_SYNONYMS)
134    Seq (Empty, (:<|), (:|>)),
135    -- $patterns
136#else
137    Seq,
138#endif
139    -- * Construction
140    empty,          -- :: Seq a
141    singleton,      -- :: a -> Seq a
142    (<|),           -- :: a -> Seq a -> Seq a
143    (|>),           -- :: Seq a -> a -> Seq a
144    (><),           -- :: Seq a -> Seq a -> Seq a
145    fromList,       -- :: [a] -> Seq a
146    fromFunction,   -- :: Int -> (Int -> a) -> Seq a
147    fromArray,      -- :: Ix i => Array i a -> Seq a
148    -- ** Repetition
149    replicate,      -- :: Int -> a -> Seq a
150    replicateA,     -- :: Applicative f => Int -> f a -> f (Seq a)
151    replicateM,     -- :: Applicative m => Int -> m a -> m (Seq a)
152    cycleTaking,    -- :: Int -> Seq a -> Seq a
153    -- ** Iterative construction
154    iterateN,       -- :: Int -> (a -> a) -> a -> Seq a
155    unfoldr,        -- :: (b -> Maybe (a, b)) -> b -> Seq a
156    unfoldl,        -- :: (b -> Maybe (b, a)) -> b -> Seq a
157    -- * Deconstruction
158    -- | Additional functions for deconstructing sequences are available
159    -- via the 'Foldable' instance of 'Seq'.
160
161    -- ** Queries
162    null,           -- :: Seq a -> Bool
163    length,         -- :: Seq a -> Int
164    -- ** Views
165    ViewL(..),
166    viewl,          -- :: Seq a -> ViewL a
167    ViewR(..),
168    viewr,          -- :: Seq a -> ViewR a
169    -- * Scans
170    scanl,          -- :: (a -> b -> a) -> a -> Seq b -> Seq a
171    scanl1,         -- :: (a -> a -> a) -> Seq a -> Seq a
172    scanr,          -- :: (a -> b -> b) -> b -> Seq a -> Seq b
173    scanr1,         -- :: (a -> a -> a) -> Seq a -> Seq a
174    -- * Sublists
175    tails,          -- :: Seq a -> Seq (Seq a)
176    inits,          -- :: Seq a -> Seq (Seq a)
177    chunksOf,       -- :: Int -> Seq a -> Seq (Seq a)
178    -- ** Sequential searches
179    takeWhileL,     -- :: (a -> Bool) -> Seq a -> Seq a
180    takeWhileR,     -- :: (a -> Bool) -> Seq a -> Seq a
181    dropWhileL,     -- :: (a -> Bool) -> Seq a -> Seq a
182    dropWhileR,     -- :: (a -> Bool) -> Seq a -> Seq a
183    spanl,          -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
184    spanr,          -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
185    breakl,         -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
186    breakr,         -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
187    partition,      -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a)
188    filter,         -- :: (a -> Bool) -> Seq a -> Seq a
189    -- * Sorting
190    sort,           -- :: Ord a => Seq a -> Seq a
191    sortBy,         -- :: (a -> a -> Ordering) -> Seq a -> Seq a
192    sortOn,         -- :: Ord b => (a -> b) -> Seq a -> Seq a
193    unstableSort,   -- :: Ord a => Seq a -> Seq a
194    unstableSortBy, -- :: (a -> a -> Ordering) -> Seq a -> Seq a
195    unstableSortOn, -- :: Ord b => (a -> b) -> Seq a -> Seq a
196    -- * Indexing
197    lookup,         -- :: Int -> Seq a -> Maybe a
198    (!?),           -- :: Seq a -> Int -> Maybe a
199    index,          -- :: Seq a -> Int -> a
200    adjust,         -- :: (a -> a) -> Int -> Seq a -> Seq a
201    adjust',        -- :: (a -> a) -> Int -> Seq a -> Seq a
202    update,         -- :: Int -> a -> Seq a -> Seq a
203    take,           -- :: Int -> Seq a -> Seq a
204    drop,           -- :: Int -> Seq a -> Seq a
205    insertAt,       -- :: Int -> a -> Seq a -> Seq a
206    deleteAt,       -- :: Int -> Seq a -> Seq a
207    splitAt,        -- :: Int -> Seq a -> (Seq a, Seq a)
208    -- ** Indexing with predicates
209    -- | These functions perform sequential searches from the left
210    -- or right ends of the sequence, returning indices of matching
211    -- elements.
212    elemIndexL,     -- :: Eq a => a -> Seq a -> Maybe Int
213    elemIndicesL,   -- :: Eq a => a -> Seq a -> [Int]
214    elemIndexR,     -- :: Eq a => a -> Seq a -> Maybe Int
215    elemIndicesR,   -- :: Eq a => a -> Seq a -> [Int]
216    findIndexL,     -- :: (a -> Bool) -> Seq a -> Maybe Int
217    findIndicesL,   -- :: (a -> Bool) -> Seq a -> [Int]
218    findIndexR,     -- :: (a -> Bool) -> Seq a -> Maybe Int
219    findIndicesR,   -- :: (a -> Bool) -> Seq a -> [Int]
220    -- * Folds
221    -- | General folds are available via the 'Foldable' instance of 'Seq'.
222    foldMapWithIndex, -- :: Monoid m => (Int -> a -> m) -> Seq a -> m
223    foldlWithIndex, -- :: (b -> Int -> a -> b) -> b -> Seq a -> b
224    foldrWithIndex, -- :: (Int -> a -> b -> b) -> b -> Seq a -> b
225    -- * Transformations
226    mapWithIndex,   -- :: (Int -> a -> b) -> Seq a -> Seq b
227    traverseWithIndex, -- :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b)
228    reverse,        -- :: Seq a -> Seq a
229    intersperse,    -- :: a -> Seq a -> Seq a
230    -- ** Zips and unzip
231    zip,            -- :: Seq a -> Seq b -> Seq (a, b)
232    zipWith,        -- :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
233    zip3,           -- :: Seq a -> Seq b -> Seq c -> Seq (a, b, c)
234    zipWith3,       -- :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d
235    zip4,           -- :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d)
236    zipWith4,       -- :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e
237    unzip,          -- :: Seq (a, b) -> (Seq a, Seq b)
238    unzipWith       -- :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c)
239    ) where
240
241import Data.Sequence.Internal
242import Data.Sequence.Internal.Sorting
243import Prelude ()
244#ifdef __HADDOCK_VERSION__
245import Control.Monad (Monad (..))
246import Control.Applicative (Applicative (..))
247import Data.Functor (Functor (..))
248#endif
249
250{- $patterns
251
252== Pattern synonyms
253
254Much like lists can be constructed and matched using the
255@:@ and @[]@ constructors, sequences can be constructed and
256matched using the 'Empty', ':<|', and ':|>' pattern synonyms.
257
258=== Note
259
260These patterns are only available with GHC version 8.0 or later,
261and version 8.2 works better with them. When writing for such recent
262versions of GHC, the patterns can be used in place of 'empty',
263'<|', '|>', 'viewl', and 'viewr'.
264
265=== __Pattern synonym examples__
266
267Import the patterns:
268
269@
270import Data.Sequence (Seq (..))
271@
272
273Look at the first three elements of a sequence
274
275@
276getFirst3 :: Seq a -> Maybe (a,a,a)
277getFirst3 (x1 :<| x2 :<| x3 :<| _xs) = Just (x1,x2,x3)
278getFirst3 _ = Nothing
279@
280
281@
282\> getFirst3 ('fromList' [1,2,3,4]) = Just (1,2,3)
283\> getFirst3 ('fromList' [1,2]) = Nothing
284@
285
286Move the last two elements from the end of the first list
287onto the beginning of the second one.
288
289@
290shift2Right :: Seq a -> Seq a -> (Seq a, Seq a)
291shift2Right Empty ys = (Empty, ys)
292shift2Right (Empty :|> x) ys = (Empty, x :<| ys)
293shift2Right (xs :|> x1 :|> x2) = (xs, x1 :<| x2 :<| ys)
294@
295
296@
297\> shift2Right ('fromList' []) ('fromList' [10]) = ('fromList' [], 'fromList' [10])
298\> shift2Right ('fromList' [9]) ('fromList' [10]) = ('fromList' [], 'fromList' [9,10])
299\> shift2Right ('fromList' [8,9]) ('fromList' [10]) = ('fromList' [], 'fromList' [8,9,10])
300\> shift2Right ('fromList' [7,8,9]) ('fromList' [10]) = ('fromList' [7], 'fromList' [8,9,10])
301@
302-}
303