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-- * 'inits', '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 certain 106-- class methods: 107-- 108-- '<$' and '*>' each take time and space proportional 109-- to the logarithm of the size of their result. 110-- 111-- '<*' takes time and space proportional to the product of the length 112-- of its first argument and the logarithm of the length of its second 113-- argument. 114-- 115-- == Warning 116-- 117-- The size of a 'Seq' must not exceed @maxBound::Int@. Violation 118-- of this condition is not detected and if the size limit is exceeded, the 119-- behaviour of the sequence is undefined. This is unlikely to occur in most 120-- applications, but some care may be required when using '><', '<*>', '*>', or 121-- '>>', particularly repeatedly and particularly in combination with 122-- 'replicate' or 'fromFunction'. 123-- 124-- == Implementation 125-- 126-- The implementation uses 2-3 finger trees annotated with sizes, 127-- as described in section 4.2 of 128-- 129-- * Ralf Hinze and Ross Paterson, 130-- [\"Finger trees: a simple general-purpose data structure\"] 131-- (http://staff.city.ac.uk/~ross/papers/FingerTree.html), 132-- /Journal of Functional Programming/ 16:2 (2006) pp 197-217. 133-- 134----------------------------------------------------------------------------- 135 136 137module Data.Sequence ( 138 -- * Finite sequences 139#if defined(DEFINE_PATTERN_SYNONYMS) 140 Seq (Empty, (:<|), (:|>)), 141 -- $patterns 142#else 143 Seq, 144#endif 145 -- * Construction 146 empty, -- :: Seq a 147 singleton, -- :: a -> Seq a 148 (<|), -- :: a -> Seq a -> Seq a 149 (|>), -- :: Seq a -> a -> Seq a 150 (><), -- :: Seq a -> Seq a -> Seq a 151 fromList, -- :: [a] -> Seq a 152 fromFunction, -- :: Int -> (Int -> a) -> Seq a 153 fromArray, -- :: Ix i => Array i a -> Seq a 154 -- ** Repetition 155 replicate, -- :: Int -> a -> Seq a 156 replicateA, -- :: Applicative f => Int -> f a -> f (Seq a) 157 replicateM, -- :: Applicative m => Int -> m a -> m (Seq a) 158 cycleTaking, -- :: Int -> Seq a -> Seq a 159 -- ** Iterative construction 160 iterateN, -- :: Int -> (a -> a) -> a -> Seq a 161 unfoldr, -- :: (b -> Maybe (a, b)) -> b -> Seq a 162 unfoldl, -- :: (b -> Maybe (b, a)) -> b -> Seq a 163 -- * Deconstruction 164 -- | Additional functions for deconstructing sequences are available 165 -- via the 'Data.Foldable.Foldable' instance of 'Seq'. 166 167 -- ** Queries 168 null, -- :: Seq a -> Bool 169 length, -- :: Seq a -> Int 170 -- ** Views 171 ViewL(..), 172 viewl, -- :: Seq a -> ViewL a 173 ViewR(..), 174 viewr, -- :: Seq a -> ViewR a 175 -- * Scans 176 scanl, -- :: (a -> b -> a) -> a -> Seq b -> Seq a 177 scanl1, -- :: (a -> a -> a) -> Seq a -> Seq a 178 scanr, -- :: (a -> b -> b) -> b -> Seq a -> Seq b 179 scanr1, -- :: (a -> a -> a) -> Seq a -> Seq a 180 -- * Sublists 181 tails, -- :: Seq a -> Seq (Seq a) 182 inits, -- :: Seq a -> Seq (Seq a) 183 chunksOf, -- :: Int -> Seq a -> Seq (Seq a) 184 -- ** Sequential searches 185 takeWhileL, -- :: (a -> Bool) -> Seq a -> Seq a 186 takeWhileR, -- :: (a -> Bool) -> Seq a -> Seq a 187 dropWhileL, -- :: (a -> Bool) -> Seq a -> Seq a 188 dropWhileR, -- :: (a -> Bool) -> Seq a -> Seq a 189 spanl, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) 190 spanr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) 191 breakl, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) 192 breakr, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) 193 partition, -- :: (a -> Bool) -> Seq a -> (Seq a, Seq a) 194 filter, -- :: (a -> Bool) -> Seq a -> Seq a 195 -- * Sorting 196 sort, -- :: Ord a => Seq a -> Seq a 197 sortBy, -- :: (a -> a -> Ordering) -> Seq a -> Seq a 198 sortOn, -- :: Ord b => (a -> b) -> Seq a -> Seq a 199 unstableSort, -- :: Ord a => Seq a -> Seq a 200 unstableSortBy, -- :: (a -> a -> Ordering) -> Seq a -> Seq a 201 unstableSortOn, -- :: Ord b => (a -> b) -> Seq a -> Seq a 202 -- * Indexing 203 lookup, -- :: Int -> Seq a -> Maybe a 204 (!?), -- :: Seq a -> Int -> Maybe a 205 index, -- :: Seq a -> Int -> a 206 adjust, -- :: (a -> a) -> Int -> Seq a -> Seq a 207 adjust', -- :: (a -> a) -> Int -> Seq a -> Seq a 208 update, -- :: Int -> a -> Seq a -> Seq a 209 take, -- :: Int -> Seq a -> Seq a 210 drop, -- :: Int -> Seq a -> Seq a 211 insertAt, -- :: Int -> a -> Seq a -> Seq a 212 deleteAt, -- :: Int -> Seq a -> Seq a 213 splitAt, -- :: Int -> Seq a -> (Seq a, Seq a) 214 -- ** Indexing with predicates 215 -- | These functions perform sequential searches from the left 216 -- or right ends of the sequence, returning indices of matching 217 -- elements. 218 elemIndexL, -- :: Eq a => a -> Seq a -> Maybe Int 219 elemIndicesL, -- :: Eq a => a -> Seq a -> [Int] 220 elemIndexR, -- :: Eq a => a -> Seq a -> Maybe Int 221 elemIndicesR, -- :: Eq a => a -> Seq a -> [Int] 222 findIndexL, -- :: (a -> Bool) -> Seq a -> Maybe Int 223 findIndicesL, -- :: (a -> Bool) -> Seq a -> [Int] 224 findIndexR, -- :: (a -> Bool) -> Seq a -> Maybe Int 225 findIndicesR, -- :: (a -> Bool) -> Seq a -> [Int] 226 -- * Folds 227 -- | General folds are available via the 'Data.Foldable.Foldable' instance 228 -- of 'Seq'. 229 foldMapWithIndex, -- :: Monoid m => (Int -> a -> m) -> Seq a -> m 230 foldlWithIndex, -- :: (b -> Int -> a -> b) -> b -> Seq a -> b 231 foldrWithIndex, -- :: (Int -> a -> b -> b) -> b -> Seq a -> b 232 -- * Transformations 233 mapWithIndex, -- :: (Int -> a -> b) -> Seq a -> Seq b 234 traverseWithIndex, -- :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) 235 reverse, -- :: Seq a -> Seq a 236 intersperse, -- :: a -> Seq a -> Seq a 237 -- ** Zips and unzip 238 zip, -- :: Seq a -> Seq b -> Seq (a, b) 239 zipWith, -- :: (a -> b -> c) -> Seq a -> Seq b -> Seq c 240 zip3, -- :: Seq a -> Seq b -> Seq c -> Seq (a, b, c) 241 zipWith3, -- :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d 242 zip4, -- :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d) 243 zipWith4, -- :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e 244 unzip, -- :: Seq (a, b) -> (Seq a, Seq b) 245 unzipWith -- :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) 246 ) where 247 248import Data.Sequence.Internal 249import Data.Sequence.Internal.Sorting 250import Prelude () 251#ifdef __HADDOCK_VERSION__ 252import Control.Monad (Monad (..)) 253import Control.Applicative (Applicative (..)) 254import Data.Functor (Functor (..)) 255#endif 256 257{- $patterns 258 259== Pattern synonyms 260 261Much like lists can be constructed and matched using the 262@:@ and @[]@ constructors, sequences can be constructed and 263matched using the 'Empty', ':<|', and ':|>' pattern synonyms. 264 265=== Note 266 267These patterns are only available with GHC version 8.0 or later, 268and version 8.2 works better with them. When writing for such recent 269versions of GHC, the patterns can be used in place of 'empty', 270'<|', '|>', 'viewl', and 'viewr'. 271 272=== __Pattern synonym examples__ 273 274Import the patterns: 275 276@ 277import Data.Sequence (Seq (..)) 278@ 279 280Look at the first three elements of a sequence 281 282@ 283getFirst3 :: Seq a -> Maybe (a,a,a) 284getFirst3 (x1 :<| x2 :<| x3 :<| _xs) = Just (x1,x2,x3) 285getFirst3 _ = Nothing 286@ 287 288@ 289\> getFirst3 ('fromList' [1,2,3,4]) = Just (1,2,3) 290\> getFirst3 ('fromList' [1,2]) = Nothing 291@ 292 293Move the last two elements from the end of the first list 294onto the beginning of the second one. 295 296@ 297shift2Right :: Seq a -> Seq a -> (Seq a, Seq a) 298shift2Right Empty ys = (Empty, ys) 299shift2Right (Empty :|> x) ys = (Empty, x :<| ys) 300shift2Right (xs :|> x1 :|> x2) ys = (xs, x1 :<| x2 :<| ys) 301@ 302 303@ 304\> shift2Right ('fromList' []) ('fromList' [10]) = ('fromList' [], 'fromList' [10]) 305\> shift2Right ('fromList' [9]) ('fromList' [10]) = ('fromList' [], 'fromList' [9,10]) 306\> shift2Right ('fromList' [8,9]) ('fromList' [10]) = ('fromList' [], 'fromList' [8,9,10]) 307\> shift2Right ('fromList' [7,8,9]) ('fromList' [10]) = ('fromList' [7], 'fromList' [8,9,10]) 308@ 309-} 310