-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Assorted concrete container types -- -- This package contains efficient general-purpose implementations of -- various immutable container types including sets, maps, sequences, -- trees, and graphs. -- -- For a walkthrough of what this package provides with examples of -- common operations see the containers introduction. -- -- The declared cost of each operation is either worst-case or amortized, -- but remains valid even if structures are shared. @package containers @version 0.6.5.1 module Utils.Containers.Internal.BitUtil bitcount :: Int -> Word -> Int -- | Return a word where only the highest bit is set. highestBitMask :: Word -> Word shiftLL :: Word -> Int -> Word shiftRL :: Word -> Int -> Word wordSize :: Int -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- An extremely light-weight, fast, and limited representation of a -- string of up to (2*WORDSIZE - 2) bits. In fact, there are two -- representations, misleadingly named bit queue builder and bit queue. -- The builder supports only emptyQB, creating an empty builder, -- and snocQB, enqueueing a bit. The bit queue builder is then -- turned into a bit queue using buildQ, after which bits can be -- removed one by one using unconsQ. If the size limit is -- exceeded, further operations will silently produce nonsense. module Utils.Containers.Internal.BitQueue data BitQueue data BitQueueB -- | Create an empty bit queue builder. This is represented as a single -- guard bit in the most significant position. emptyQB :: BitQueueB -- | Enqueue a bit. This works by shifting the queue right one bit, then -- setting the most significant bit as requested. snocQB :: BitQueueB -> Bool -> BitQueueB -- | Convert a bit queue builder to a bit queue. This shifts in a new guard -- bit on the left, and shifts right until the old guard bit falls off. buildQ :: BitQueueB -> BitQueue -- | Dequeue an element, or discover the queue is empty. unconsQ :: BitQueue -> Maybe (Bool, BitQueue) -- | Convert a bit queue to a list of bits by unconsing. This is used to -- test that the queue functions properly. toListQ :: BitQueue -> [Bool] instance GHC.Show.Show Utils.Containers.Internal.BitQueue.BitQueue instance GHC.Show.Show Utils.Containers.Internal.BitQueue.BitQueueB -- | A strict pair module Utils.Containers.Internal.StrictPair -- | The same as a regular Haskell pair, but -- --
--   (x :*: _|_) = (_|_ :*: y) = _|_
--   
data StrictPair a b (:*:) :: !a -> !b -> StrictPair a b infixr 1 :*: -- | Convert a strict pair to a standard pair. toPair :: StrictPair a b -> (a, b) -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- An efficient implementation of sets. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import Data.Set (Set)
--   import qualified Data.Set as Set
--   
-- -- The implementation of Set is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- -- -- Note that the implementation is left-biased -- the elements of -- a first argument are always preferred to the second, for example in -- union or insert. Of course, left-biasing can only be -- observed when equality is an equivalence relation instead of -- structural equality. -- -- Warning: The size of the set must not exceed -- maxBound::Int. Violation of this condition is not detected -- and if the size limit is exceeded, the behavior of the set is -- completely undefined. module Data.Set.Internal -- | A set of values a. data Set a Bin :: {-# UNPACK #-} !Size -> !a -> !Set a -> !Set a -> Set a Tip :: Set a type Size = Int -- | O(m*log(n/m+1)), m <= n. See difference. (\\) :: Ord a => Set a -> Set a -> Set a infixl 9 \\ -- | O(1). Is this the empty set? null :: Set a -> Bool -- | O(1). The number of elements in the set. size :: Set a -> Int -- | O(log n). Is the element in the set? member :: Ord a => a -> Set a -> Bool -- | O(log n). Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool -- | O(log n). Find largest element smaller than the given one. -- --
--   lookupLT 3 (fromList [3, 5]) == Nothing
--   lookupLT 5 (fromList [3, 5]) == Just 3
--   
lookupLT :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find smallest element greater than the given one. -- --
--   lookupGT 4 (fromList [3, 5]) == Just 5
--   lookupGT 5 (fromList [3, 5]) == Nothing
--   
lookupGT :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find largest element smaller or equal to the given -- one. -- --
--   lookupLE 2 (fromList [3, 5]) == Nothing
--   lookupLE 4 (fromList [3, 5]) == Just 3
--   lookupLE 5 (fromList [3, 5]) == Just 5
--   
lookupLE :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find smallest element greater or equal to the given -- one. -- --
--   lookupGE 3 (fromList [3, 5]) == Just 3
--   lookupGE 4 (fromList [3, 5]) == Just 5
--   lookupGE 6 (fromList [3, 5]) == Nothing
--   
lookupGE :: Ord a => a -> Set a -> Maybe a -- | O(m*log(n/m + 1)), m <= n. (s1 `isSubsetOf` s2) -- indicates whether s1 is a subset of s2. -- --
--   s1 `isSubsetOf` s2 = all (`member` s2) s1
--   s1 `isSubsetOf` s2 = null (s1 `difference` s2)
--   s1 `isSubsetOf` s2 = s1 `union` s2 == s2
--   s1 `isSubsetOf` s2 = s1 `intersection` s2 == s1
--   
isSubsetOf :: Ord a => Set a -> Set a -> Bool -- | O(m*log(n/m + 1)), m <= n. (s1 `isProperSubsetOf` -- s2) indicates whether s1 is a proper subset of -- s2. -- --
--   s1 `isProperSubsetOf` s2 = s1 `isSubsetOf` s2 && s1 /= s2
--   
isProperSubsetOf :: Ord a => Set a -> Set a -> Bool -- | O(m*log(n/m + 1)), m <= n. Check whether two sets are -- disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [2,4,6])   (fromList [1,3])     == True
--   disjoint (fromList [2,4,6,8]) (fromList [2,3,5,7]) == False
--   disjoint (fromList [1,2])     (fromList [1,2,3,4]) == False
--   disjoint (fromList [])        (fromList [])        == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord a => Set a -> Set a -> Bool -- | O(1). The empty set. empty :: Set a -- | O(1). Create a singleton set. singleton :: a -> Set a -- | O(log n). Insert an element in a set. If the set already -- contains an element equal to the given value, it is replaced with the -- new value. insert :: Ord a => a -> Set a -> Set a -- | O(log n). Delete an element from a set. delete :: Ord a => a -> Set a -> Set a -- | O(log n) (alterF f x s) can delete or insert -- x in s depending on whether an equal element is -- found in s. -- -- In short: -- --
--   member x <$> alterF f x s = f (member x s)
--   
-- -- Note that unlike insert, alterF will not replace -- an element equal to the given value. -- -- Note: alterF is a variant of the at combinator from -- Control.Lens.At. alterF :: (Ord a, Functor f) => (Bool -> f Bool) -> a -> Set a -> f (Set a) -- | Calculate the power set of a set: the set of all its subsets. -- --
--   t `member` powerSet s == t `isSubsetOf` s
--   
-- -- Example: -- --
--   powerSet (fromList [1,2,3]) =
--     fromList $ map fromList [[],[1],[1,2],[1,2,3],[1,3],[2],[2,3],[3]]
--   
powerSet :: Set a -> Set (Set a) -- | O(m*log(n/m + 1)), m <= n. The union of two sets, preferring -- the first set when equal elements are encountered. union :: Ord a => Set a -> Set a -> Set a -- | The union of the sets in a Foldable structure : (unions == -- foldl union empty). unions :: (Foldable f, Ord a) => f (Set a) -> Set a -- | O(m*log(n/m + 1)), m <= n. Difference of two sets. -- -- Return elements of the first set not existing in the second set. -- --
--   difference (fromList [5, 3]) (fromList [5, 7]) == singleton 3
--   
difference :: Ord a => Set a -> Set a -> Set a -- | O(m*log(n/m + 1)), m <= n. The intersection of two sets. -- Elements of the result come from the first set, so for example -- --
--   import qualified Data.Set as S
--   data AB = A | B deriving Show
--   instance Ord AB where compare _ _ = EQ
--   instance Eq AB where _ == _ = True
--   main = print (S.singleton A `S.intersection` S.singleton B,
--                 S.singleton B `S.intersection` S.singleton A)
--   
-- -- prints (fromList [A],fromList [B]). intersection :: Ord a => Set a -> Set a -> Set a -- | O(m*n) (conjectured). Calculate the Cartesian product of two -- sets. -- --
--   cartesianProduct xs ys = fromList $ liftA2 (,) (toList xs) (toList ys)
--   
-- -- Example: -- --
--   cartesianProduct (fromList [1,2]) (fromList ['a','b']) =
--     fromList [(1,'a'), (1,'b'), (2,'a'), (2,'b')]
--   
cartesianProduct :: Set a -> Set b -> Set (a, b) -- | Calculate the disjoint union of two sets. -- --
--   disjointUnion xs ys = map Left xs `union` map Right ys
--   
-- -- Example: -- --
--   disjointUnion (fromList [1,2]) (fromList ["hi", "bye"]) =
--     fromList [Left 1, Left 2, Right "hi", Right "bye"]
--   
disjointUnion :: Set a -> Set b -> Set (Either a b) -- | O(n). Filter all elements that satisfy the predicate. filter :: (a -> Bool) -> Set a -> Set a -- | O(log n). Take while a predicate on the elements holds. The -- user is responsible for ensuring that for all elements j and -- k in the set, j < k ==> p j >= p k. See -- note at spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile p . toList
--   takeWhileAntitone p = filter p
--   
takeWhileAntitone :: (a -> Bool) -> Set a -> Set a -- | O(log n). Drop while a predicate on the elements holds. The -- user is responsible for ensuring that for all elements j and -- k in the set, j < k ==> p j >= p k. See -- note at spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile p . toList
--   dropWhileAntitone p = filter (not . p)
--   
dropWhileAntitone :: (a -> Bool) -> Set a -> Set a -- | O(log n). Divide a set at the point where a predicate on the -- elements stops holding. The user is responsible for ensuring that for -- all elements j and k in the set, j < k ==> -- p j >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partition p xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the set at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first element and to fail -- after the last element). spanAntitone :: (a -> Bool) -> Set a -> (Set a, Set a) -- | O(n). Partition the set into two sets, one with all elements -- that satisfy the predicate and one with all elements that don't -- satisfy the predicate. See also split. partition :: (a -> Bool) -> Set a -> (Set a, Set a) -- | O(log n). The expression (split x set) is a -- pair (set1,set2) where set1 comprises the elements -- of set less than x and set2 comprises the -- elements of set greater than x. split :: Ord a => a -> Set a -> (Set a, Set a) -- | O(log n). Performs a split but also returns whether the -- pivot element was found in the original set. splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a) -- | O(1). Decompose a set into pieces based on the structure of the -- underlying tree. This function is useful for consuming a set in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first subset less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList [1..6]) ==
--     [fromList [1,2,3],fromList [4],fromList [5,6]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- subsets, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Set a -> [Set a] -- | O(log n). Lookup the index of an element, which is its -- zero-based index in the sorted sequence of elements. The index is a -- number from 0 up to, but not including, the size of the -- set. -- --
--   isJust   (lookupIndex 2 (fromList [5,3])) == False
--   fromJust (lookupIndex 3 (fromList [5,3])) == 0
--   fromJust (lookupIndex 5 (fromList [5,3])) == 1
--   isJust   (lookupIndex 6 (fromList [5,3])) == False
--   
lookupIndex :: Ord a => a -> Set a -> Maybe Int -- | O(log n). Return the index of an element, which is its -- zero-based index in the sorted sequence of elements. The index is a -- number from 0 up to, but not including, the size of the -- set. Calls error when the element is not a member of the -- set. -- --
--   findIndex 2 (fromList [5,3])    Error: element is not in the set
--   findIndex 3 (fromList [5,3]) == 0
--   findIndex 5 (fromList [5,3]) == 1
--   findIndex 6 (fromList [5,3])    Error: element is not in the set
--   
findIndex :: Ord a => a -> Set a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sorted sequence of elements. If the -- index is out of range (less than zero, greater or equal to -- size of the set), error is called. -- --
--   elemAt 0 (fromList [5,3]) == 3
--   elemAt 1 (fromList [5,3]) == 5
--   elemAt 2 (fromList [5,3])    Error: index out of range
--   
elemAt :: Int -> Set a -> a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sorted sequence of elements. If the -- index is out of range (less than zero, greater or equal to -- size of the set), error is called. -- --
--   deleteAt 0    (fromList [5,3]) == singleton 5
--   deleteAt 1    (fromList [5,3]) == singleton 3
--   deleteAt 2    (fromList [5,3])    Error: index out of range
--   deleteAt (-1) (fromList [5,3])    Error: index out of range
--   
deleteAt :: Int -> Set a -> Set a -- | Take a given number of elements in order, beginning with the smallest -- ones. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Set a -> Set a -- | Drop a given number of elements in order, beginning with the smallest -- ones. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Set a -> Set a -- | O(log n). Split a set at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Set a -> (Set a, Set a) -- | O(n*log n). map f s is the set obtained by -- applying f to each element of s. -- -- It's worth noting that the size of the result may be smaller if, for -- some (x,y), x /= y && f x == f y map :: Ord b => (a -> b) -> Set a -> Set b -- | O(n). The -- -- mapMonotonic f s == map f s, but works only -- when f is strictly increasing. The precondition is not -- checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapMonotonic f s == map f s
--       where ls = toList s
--   
mapMonotonic :: (a -> b) -> Set a -> Set b -- | O(n). Fold the elements in the set using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . toAscList. -- -- For example, -- --
--   toAscList set = foldr (:) [] set
--   
foldr :: (a -> b -> b) -> b -> Set a -> b -- | O(n). Fold the elements in the set using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . toAscList. -- -- For example, -- --
--   toDescList set = foldl (flip (:)) [] set
--   
foldl :: (a -> b -> a) -> a -> Set b -> a -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Set a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Set b -> a -- | O(n). Fold the elements in the set using the given -- right-associative binary operator. This function is an equivalent of -- foldr and is present for compatibility only. -- -- Please note that fold will be deprecated in the future and -- removed. fold :: (a -> b -> b) -> b -> Set a -> b -- | O(log n). The minimal element of a set. lookupMin :: Set a -> Maybe a -- | O(log n). The maximal element of a set. lookupMax :: Set a -> Maybe a -- | O(log n). The minimal element of a set. findMin :: Set a -> a -- | O(log n). The maximal element of a set. findMax :: Set a -> a -- | O(log n). Delete the minimal element. Returns an empty set if -- the set is empty. deleteMin :: Set a -> Set a -- | O(log n). Delete the maximal element. Returns an empty set if -- the set is empty. deleteMax :: Set a -> Set a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin set = (findMin set, deleteMin set)
--   
deleteFindMin :: Set a -> (a, Set a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax set = (findMax set, deleteMax set)
--   
deleteFindMax :: Set a -> (a, Set a) -- | O(log n). Retrieves the maximal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. maxView :: Set a -> Maybe (a, Set a) -- | O(log n). Retrieves the minimal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. minView :: Set a -> Maybe (a, Set a) -- | O(n). An alias of toAscList. The elements of a set in -- ascending order. Subject to list fusion. elems :: Set a -> [a] -- | O(n). Convert the set to a list of elements. Subject to list -- fusion. toList :: Set a -> [a] -- | O(n*log n). Create a set from a list of elements. -- -- If the elements are ordered, a linear-time implementation is used, -- with the performance equal to fromDistinctAscList. fromList :: Ord a => [a] -> Set a -- | O(n). Convert the set to an ascending list of elements. Subject -- to list fusion. toAscList :: Set a -> [a] -- | O(n). Convert the set to a descending list of elements. Subject -- to list fusion. toDescList :: Set a -> [a] -- | O(n). Build a set from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. fromAscList :: Eq a => [a] -> Set a -- | O(n). Build a set from an ascending list of distinct elements -- in linear time. The precondition (input list is strictly ascending) -- is not checked. fromDistinctAscList :: [a] -> Set a -- | O(n). Build a set from a descending list in linear time. The -- precondition (input list is descending) is not checked. fromDescList :: Eq a => [a] -> Set a -- | O(n). Build a set from a descending list of distinct elements -- in linear time. The precondition (input list is strictly -- descending) is not checked. fromDistinctDescList :: [a] -> Set a -- | O(n). Show the tree that implements the set. The tree is shown -- in a compressed, hanging format. showTree :: Show a => Set a -> String -- | O(n). The expression (showTreeWith hang wide map) -- shows the tree that implements the set. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. -- --
--   Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5]
--   4
--   +--2
--   |  +--1
--   |  +--3
--   +--5
--   
--   Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1..5]
--   4
--   |
--   +--2
--   |  |
--   |  +--1
--   |  |
--   |  +--3
--   |
--   +--5
--   
--   Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1..5]
--   +--5
--   |
--   4
--   |
--   |  +--3
--   |  |
--   +--2
--      |
--      +--1
--   
showTreeWith :: Show a => Bool -> Bool -> Set a -> String -- | O(n). Test if the internal set structure is valid. valid :: Ord a => Set a -> Bool bin :: a -> Set a -> Set a -> Set a balanced :: Set a -> Bool link :: a -> Set a -> Set a -> Set a merge :: Set a -> Set a -> Set a instance GHC.Base.Semigroup (Data.Set.Internal.MergeSet a) instance GHC.Base.Monoid (Data.Set.Internal.MergeSet a) instance GHC.Classes.Ord a => GHC.Base.Monoid (Data.Set.Internal.Set a) instance GHC.Classes.Ord a => GHC.Base.Semigroup (Data.Set.Internal.Set a) instance Data.Foldable.Foldable Data.Set.Internal.Set instance (Data.Data.Data a, GHC.Classes.Ord a) => Data.Data.Data (Data.Set.Internal.Set a) instance GHC.Classes.Ord a => GHC.Exts.IsList (Data.Set.Internal.Set a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Set.Internal.Set a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Set.Internal.Set a) instance GHC.Show.Show a => GHC.Show.Show (Data.Set.Internal.Set a) instance Data.Functor.Classes.Eq1 Data.Set.Internal.Set instance Data.Functor.Classes.Ord1 Data.Set.Internal.Set instance Data.Functor.Classes.Show1 Data.Set.Internal.Set instance (GHC.Read.Read a, GHC.Classes.Ord a) => GHC.Read.Read (Data.Set.Internal.Set a) instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Set.Internal.Set a) -- |

Finite Sets

-- -- The Set e type represents a set of elements of type -- e. Most operations require that e be an instance of -- the Ord class. A Set is strict in its elements. -- -- For a walkthrough of the most commonly used functions see the sets -- introduction. -- -- Note that the implementation is generally left-biased. -- Functions that take two sets as arguments and combine them, such as -- union and intersection, prefer the entries in the first -- argument to those in the second. Of course, this bias can only be -- observed when equality is an equivalence relation instead of -- structural equality. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import Data.Set (Set)
--   import qualified Data.Set as Set
--   
-- --

Warning

-- -- The size of the set must not exceed maxBound::Int. Violation -- of this condition is not detected and if the size limit is exceeded, -- its behaviour is undefined. -- --

Implementation

-- -- The implementation of Set is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- module Data.Set -- | A set of values a. data Set a -- | O(1). The empty set. empty :: Set a -- | O(1). Create a singleton set. singleton :: a -> Set a -- | O(n*log n). Create a set from a list of elements. -- -- If the elements are ordered, a linear-time implementation is used, -- with the performance equal to fromDistinctAscList. fromList :: Ord a => [a] -> Set a -- | O(n). Build a set from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. fromAscList :: Eq a => [a] -> Set a -- | O(n). Build a set from a descending list in linear time. The -- precondition (input list is descending) is not checked. fromDescList :: Eq a => [a] -> Set a -- | O(n). Build a set from an ascending list of distinct elements -- in linear time. The precondition (input list is strictly ascending) -- is not checked. fromDistinctAscList :: [a] -> Set a -- | O(n). Build a set from a descending list of distinct elements -- in linear time. The precondition (input list is strictly -- descending) is not checked. fromDistinctDescList :: [a] -> Set a -- | Calculate the power set of a set: the set of all its subsets. -- --
--   t `member` powerSet s == t `isSubsetOf` s
--   
-- -- Example: -- --
--   powerSet (fromList [1,2,3]) =
--     fromList $ map fromList [[],[1],[1,2],[1,2,3],[1,3],[2],[2,3],[3]]
--   
powerSet :: Set a -> Set (Set a) -- | O(log n). Insert an element in a set. If the set already -- contains an element equal to the given value, it is replaced with the -- new value. insert :: Ord a => a -> Set a -> Set a -- | O(log n). Delete an element from a set. delete :: Ord a => a -> Set a -> Set a -- | O(log n) (alterF f x s) can delete or insert -- x in s depending on whether an equal element is -- found in s. -- -- In short: -- --
--   member x <$> alterF f x s = f (member x s)
--   
-- -- Note that unlike insert, alterF will not replace -- an element equal to the given value. -- -- Note: alterF is a variant of the at combinator from -- Control.Lens.At. alterF :: (Ord a, Functor f) => (Bool -> f Bool) -> a -> Set a -> f (Set a) -- | O(log n). Is the element in the set? member :: Ord a => a -> Set a -> Bool -- | O(log n). Is the element not in the set? notMember :: Ord a => a -> Set a -> Bool -- | O(log n). Find largest element smaller than the given one. -- --
--   lookupLT 3 (fromList [3, 5]) == Nothing
--   lookupLT 5 (fromList [3, 5]) == Just 3
--   
lookupLT :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find smallest element greater than the given one. -- --
--   lookupGT 4 (fromList [3, 5]) == Just 5
--   lookupGT 5 (fromList [3, 5]) == Nothing
--   
lookupGT :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find largest element smaller or equal to the given -- one. -- --
--   lookupLE 2 (fromList [3, 5]) == Nothing
--   lookupLE 4 (fromList [3, 5]) == Just 3
--   lookupLE 5 (fromList [3, 5]) == Just 5
--   
lookupLE :: Ord a => a -> Set a -> Maybe a -- | O(log n). Find smallest element greater or equal to the given -- one. -- --
--   lookupGE 3 (fromList [3, 5]) == Just 3
--   lookupGE 4 (fromList [3, 5]) == Just 5
--   lookupGE 6 (fromList [3, 5]) == Nothing
--   
lookupGE :: Ord a => a -> Set a -> Maybe a -- | O(1). Is this the empty set? null :: Set a -> Bool -- | O(1). The number of elements in the set. size :: Set a -> Int -- | O(m*log(n/m + 1)), m <= n. (s1 `isSubsetOf` s2) -- indicates whether s1 is a subset of s2. -- --
--   s1 `isSubsetOf` s2 = all (`member` s2) s1
--   s1 `isSubsetOf` s2 = null (s1 `difference` s2)
--   s1 `isSubsetOf` s2 = s1 `union` s2 == s2
--   s1 `isSubsetOf` s2 = s1 `intersection` s2 == s1
--   
isSubsetOf :: Ord a => Set a -> Set a -> Bool -- | O(m*log(n/m + 1)), m <= n. (s1 `isProperSubsetOf` -- s2) indicates whether s1 is a proper subset of -- s2. -- --
--   s1 `isProperSubsetOf` s2 = s1 `isSubsetOf` s2 && s1 /= s2
--   
isProperSubsetOf :: Ord a => Set a -> Set a -> Bool -- | O(m*log(n/m + 1)), m <= n. Check whether two sets are -- disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [2,4,6])   (fromList [1,3])     == True
--   disjoint (fromList [2,4,6,8]) (fromList [2,3,5,7]) == False
--   disjoint (fromList [1,2])     (fromList [1,2,3,4]) == False
--   disjoint (fromList [])        (fromList [])        == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord a => Set a -> Set a -> Bool -- | O(m*log(n/m + 1)), m <= n. The union of two sets, preferring -- the first set when equal elements are encountered. union :: Ord a => Set a -> Set a -> Set a -- | The union of the sets in a Foldable structure : (unions == -- foldl union empty). unions :: (Foldable f, Ord a) => f (Set a) -> Set a -- | O(m*log(n/m + 1)), m <= n. Difference of two sets. -- -- Return elements of the first set not existing in the second set. -- --
--   difference (fromList [5, 3]) (fromList [5, 7]) == singleton 3
--   
difference :: Ord a => Set a -> Set a -> Set a -- | O(m*log(n/m+1)), m <= n. See difference. (\\) :: Ord a => Set a -> Set a -> Set a infixl 9 \\ -- | O(m*log(n/m + 1)), m <= n. The intersection of two sets. -- Elements of the result come from the first set, so for example -- --
--   import qualified Data.Set as S
--   data AB = A | B deriving Show
--   instance Ord AB where compare _ _ = EQ
--   instance Eq AB where _ == _ = True
--   main = print (S.singleton A `S.intersection` S.singleton B,
--                 S.singleton B `S.intersection` S.singleton A)
--   
-- -- prints (fromList [A],fromList [B]). intersection :: Ord a => Set a -> Set a -> Set a -- | O(m*n) (conjectured). Calculate the Cartesian product of two -- sets. -- --
--   cartesianProduct xs ys = fromList $ liftA2 (,) (toList xs) (toList ys)
--   
-- -- Example: -- --
--   cartesianProduct (fromList [1,2]) (fromList ['a','b']) =
--     fromList [(1,'a'), (1,'b'), (2,'a'), (2,'b')]
--   
cartesianProduct :: Set a -> Set b -> Set (a, b) -- | Calculate the disjoint union of two sets. -- --
--   disjointUnion xs ys = map Left xs `union` map Right ys
--   
-- -- Example: -- --
--   disjointUnion (fromList [1,2]) (fromList ["hi", "bye"]) =
--     fromList [Left 1, Left 2, Right "hi", Right "bye"]
--   
disjointUnion :: Set a -> Set b -> Set (Either a b) -- | O(n). Filter all elements that satisfy the predicate. filter :: (a -> Bool) -> Set a -> Set a -- | O(log n). Take while a predicate on the elements holds. The -- user is responsible for ensuring that for all elements j and -- k in the set, j < k ==> p j >= p k. See -- note at spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile p . toList
--   takeWhileAntitone p = filter p
--   
takeWhileAntitone :: (a -> Bool) -> Set a -> Set a -- | O(log n). Drop while a predicate on the elements holds. The -- user is responsible for ensuring that for all elements j and -- k in the set, j < k ==> p j >= p k. See -- note at spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile p . toList
--   dropWhileAntitone p = filter (not . p)
--   
dropWhileAntitone :: (a -> Bool) -> Set a -> Set a -- | O(log n). Divide a set at the point where a predicate on the -- elements stops holding. The user is responsible for ensuring that for -- all elements j and k in the set, j < k ==> -- p j >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partition p xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the set at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first element and to fail -- after the last element). spanAntitone :: (a -> Bool) -> Set a -> (Set a, Set a) -- | O(n). Partition the set into two sets, one with all elements -- that satisfy the predicate and one with all elements that don't -- satisfy the predicate. See also split. partition :: (a -> Bool) -> Set a -> (Set a, Set a) -- | O(log n). The expression (split x set) is a -- pair (set1,set2) where set1 comprises the elements -- of set less than x and set2 comprises the -- elements of set greater than x. split :: Ord a => a -> Set a -> (Set a, Set a) -- | O(log n). Performs a split but also returns whether the -- pivot element was found in the original set. splitMember :: Ord a => a -> Set a -> (Set a, Bool, Set a) -- | O(1). Decompose a set into pieces based on the structure of the -- underlying tree. This function is useful for consuming a set in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first subset less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList [1..6]) ==
--     [fromList [1,2,3],fromList [4],fromList [5,6]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- subsets, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Set a -> [Set a] -- | O(log n). Lookup the index of an element, which is its -- zero-based index in the sorted sequence of elements. The index is a -- number from 0 up to, but not including, the size of the -- set. -- --
--   isJust   (lookupIndex 2 (fromList [5,3])) == False
--   fromJust (lookupIndex 3 (fromList [5,3])) == 0
--   fromJust (lookupIndex 5 (fromList [5,3])) == 1
--   isJust   (lookupIndex 6 (fromList [5,3])) == False
--   
lookupIndex :: Ord a => a -> Set a -> Maybe Int -- | O(log n). Return the index of an element, which is its -- zero-based index in the sorted sequence of elements. The index is a -- number from 0 up to, but not including, the size of the -- set. Calls error when the element is not a member of the -- set. -- --
--   findIndex 2 (fromList [5,3])    Error: element is not in the set
--   findIndex 3 (fromList [5,3]) == 0
--   findIndex 5 (fromList [5,3]) == 1
--   findIndex 6 (fromList [5,3])    Error: element is not in the set
--   
findIndex :: Ord a => a -> Set a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sorted sequence of elements. If the -- index is out of range (less than zero, greater or equal to -- size of the set), error is called. -- --
--   elemAt 0 (fromList [5,3]) == 3
--   elemAt 1 (fromList [5,3]) == 5
--   elemAt 2 (fromList [5,3])    Error: index out of range
--   
elemAt :: Int -> Set a -> a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sorted sequence of elements. If the -- index is out of range (less than zero, greater or equal to -- size of the set), error is called. -- --
--   deleteAt 0    (fromList [5,3]) == singleton 5
--   deleteAt 1    (fromList [5,3]) == singleton 3
--   deleteAt 2    (fromList [5,3])    Error: index out of range
--   deleteAt (-1) (fromList [5,3])    Error: index out of range
--   
deleteAt :: Int -> Set a -> Set a -- | Take a given number of elements in order, beginning with the smallest -- ones. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Set a -> Set a -- | Drop a given number of elements in order, beginning with the smallest -- ones. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Set a -> Set a -- | O(log n). Split a set at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Set a -> (Set a, Set a) -- | O(n*log n). map f s is the set obtained by -- applying f to each element of s. -- -- It's worth noting that the size of the result may be smaller if, for -- some (x,y), x /= y && f x == f y map :: Ord b => (a -> b) -> Set a -> Set b -- | O(n). The -- -- mapMonotonic f s == map f s, but works only -- when f is strictly increasing. The precondition is not -- checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapMonotonic f s == map f s
--       where ls = toList s
--   
mapMonotonic :: (a -> b) -> Set a -> Set b -- | O(n). Fold the elements in the set using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . toAscList. -- -- For example, -- --
--   toAscList set = foldr (:) [] set
--   
foldr :: (a -> b -> b) -> b -> Set a -> b -- | O(n). Fold the elements in the set using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . toAscList. -- -- For example, -- --
--   toDescList set = foldl (flip (:)) [] set
--   
foldl :: (a -> b -> a) -> a -> Set b -> a -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Set a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Set b -> a -- | O(n). Fold the elements in the set using the given -- right-associative binary operator. This function is an equivalent of -- foldr and is present for compatibility only. -- -- Please note that fold will be deprecated in the future and -- removed. fold :: (a -> b -> b) -> b -> Set a -> b -- | O(log n). The minimal element of a set. lookupMin :: Set a -> Maybe a -- | O(log n). The maximal element of a set. lookupMax :: Set a -> Maybe a -- | O(log n). The minimal element of a set. findMin :: Set a -> a -- | O(log n). The maximal element of a set. findMax :: Set a -> a -- | O(log n). Delete the minimal element. Returns an empty set if -- the set is empty. deleteMin :: Set a -> Set a -- | O(log n). Delete the maximal element. Returns an empty set if -- the set is empty. deleteMax :: Set a -> Set a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin set = (findMin set, deleteMin set)
--   
deleteFindMin :: Set a -> (a, Set a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax set = (findMax set, deleteMax set)
--   
deleteFindMax :: Set a -> (a, Set a) -- | O(log n). Retrieves the maximal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. maxView :: Set a -> Maybe (a, Set a) -- | O(log n). Retrieves the minimal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. minView :: Set a -> Maybe (a, Set a) -- | O(n). An alias of toAscList. The elements of a set in -- ascending order. Subject to list fusion. elems :: Set a -> [a] -- | O(n). Convert the set to a list of elements. Subject to list -- fusion. toList :: Set a -> [a] -- | O(n). Convert the set to an ascending list of elements. Subject -- to list fusion. toAscList :: Set a -> [a] -- | O(n). Convert the set to a descending list of elements. Subject -- to list fusion. toDescList :: Set a -> [a] -- | O(n). Show the tree that implements the set. The tree is shown -- in a compressed, hanging format. showTree :: Show a => Set a -> String -- | O(n). The expression (showTreeWith hang wide map) -- shows the tree that implements the set. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. -- --
--   Set> putStrLn $ showTreeWith True False $ fromDistinctAscList [1..5]
--   4
--   +--2
--   |  +--1
--   |  +--3
--   +--5
--   
--   Set> putStrLn $ showTreeWith True True $ fromDistinctAscList [1..5]
--   4
--   |
--   +--2
--   |  |
--   |  +--1
--   |  |
--   |  +--3
--   |
--   +--5
--   
--   Set> putStrLn $ showTreeWith False True $ fromDistinctAscList [1..5]
--   +--5
--   |
--   4
--   |
--   |  +--3
--   |  |
--   +--2
--      |
--      +--1
--   
showTreeWith :: Show a => Bool -> Bool -> Set a -> String -- | O(n). Test if the internal set structure is valid. valid :: Ord a => Set a -> Bool -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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 -- <math> referring to the length of the sequence and <math> -- 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. module Data.Sequence.Internal newtype Elem a Elem :: a -> Elem a [getElem] :: Elem a -> a data FingerTree a EmptyT :: FingerTree a Single :: a -> FingerTree a Deep :: {-# UNPACK #-} !Int -> !Digit a -> FingerTree (Node a) -> !Digit a -> FingerTree a data Node a Node2 :: {-# UNPACK #-} !Int -> a -> a -> Node a Node3 :: {-# UNPACK #-} !Int -> a -> a -> a -> Node a data Digit a One :: a -> Digit a Two :: a -> a -> Digit a Three :: a -> a -> a -> Digit a Four :: a -> a -> a -> a -> Digit a class Sized a size :: Sized a => a -> Int class MaybeForce a -- | General-purpose finite sequences. newtype Seq a Seq :: FingerTree (Elem a) -> Seq a -- | A bidirectional pattern synonym matching an empty sequence. pattern Empty :: Seq a -- | A bidirectional pattern synonym viewing the front of a non-empty -- sequence. pattern (:<|) :: a -> Seq a -> Seq a -- | A bidirectional pattern synonym viewing the rear of a non-empty -- sequence. pattern (:|>) :: Seq a -> a -> Seq a infixr 5 :<| infixl 5 :|> newtype State s a State :: (s -> (s, a)) -> State s a [runState] :: State s a -> s -> (s, a) execState :: State s a -> s -> a foldDigit :: (b -> b -> b) -> (a -> b) -> Digit a -> b foldNode :: (b -> b -> b) -> (a -> b) -> Node a -> b foldWithIndexDigit :: Sized a => (b -> b -> b) -> (Int -> a -> b) -> Int -> Digit a -> b foldWithIndexNode :: Sized a => (m -> m -> m) -> (Int -> a -> m) -> Int -> Node a -> m -- | <math>. The empty sequence. empty :: Seq a -- | <math>. A singleton sequence. singleton :: a -> Seq a -- | <math>. Add an element to the left end of a sequence. Mnemonic: -- a triangle with the single element at the pointy end. (<|) :: a -> Seq a -> Seq a infixr 5 <| -- | <math>. Add an element to the right end of a sequence. Mnemonic: -- a triangle with the single element at the pointy end. (|>) :: Seq a -> a -> Seq a infixl 5 |> -- | <math>. Concatenate two sequences. (><) :: Seq a -> Seq a -> Seq a infixr 5 >< -- | <math>. 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. fromList :: [a] -> Seq a -- | <math>. Convert a given sequence length and a function -- representing that sequence into a sequence. fromFunction :: Int -> (Int -> a) -> Seq a -- | <math>. 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. fromArray :: Ix i => Array i a -> Seq a -- | <math>. replicate n x is a sequence consisting of -- n copies of x. replicate :: Int -> a -> Seq a -- | replicateA is an Applicative version of -- replicate, and makes <math> calls to liftA2 and -- pure. -- --
--   replicateA n x = sequenceA (replicate n x)
--   
replicateA :: Applicative f => Int -> f a -> f (Seq a) -- | 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. replicateM :: Applicative m => Int -> m a -> m (Seq a) -- | 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
--   
cycleTaking :: Int -> Seq a -> Seq a -- | <math>. 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))
--   
iterateN :: Int -> (a -> a) -> a -> 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. unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a -- | unfoldl f x is equivalent to reverse -- (unfoldr (fmap swap . f) x). unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a -- | <math>. Is this the empty sequence? null :: Seq a -> Bool -- | <math>. The number of elements in the sequence. length :: Seq a -> Int -- | View of the left end of a sequence. data ViewL a -- | empty sequence EmptyL :: ViewL a -- | leftmost element and the rest of the sequence (:<) :: a -> Seq a -> ViewL a infixr 5 :< -- | <math>. Analyse the left end of a sequence. viewl :: Seq a -> ViewL a -- | View of the right end of a sequence. data ViewR a -- | empty sequence EmptyR :: ViewR a -- | the sequence minus the rightmost element, and the rightmost element (:>) :: Seq a -> a -> ViewR a infixl 5 :> -- | <math>. Analyse the right end of a sequence. viewr :: Seq a -> ViewR a -- | 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, ...]
--   
scanl :: (a -> b -> a) -> a -> Seq b -> Seq a -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f (fromList [x1, x2, ...]) = fromList [x1, x1 `f` x2, ...]
--   
scanl1 :: (a -> a -> a) -> Seq a -> Seq a -- | scanr is the right-to-left dual of scanl. scanr :: (a -> b -> b) -> b -> Seq a -> Seq b -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> Seq a -> Seq a -- | <math>. 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 <math>th suffix takes <math>, but -- evaluating every suffix in the sequence takes <math> due to -- sharing. tails :: Seq a -> Seq (Seq a) -- | <math>. 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 <math>th prefix takes <math>, but -- evaluating every prefix in the sequence takes <math> due to -- sharing. inits :: Seq a -> Seq (Seq a) -- | <math>. 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 -- <math> (for <math>) to <math> (for <math>). -- The true bound is more like <math> chunksOf :: Int -> Seq a -> Seq (Seq a) -- | <math> where <math> 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. takeWhileL :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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)). takeWhileR :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> is the prefix length. -- dropWhileL p xs returns the suffix remaining after -- takeWhileL p xs. dropWhileL :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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)). dropWhileR :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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. spanl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math> where <math> 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. spanr :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math> where <math> 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). breakl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | breakr p is equivalent to spanr (not . -- p). breakr :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math>. 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. partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math>. The filter function takes a predicate p -- and a sequence xs and returns a sequence of those elements -- which satisfy the predicate. filter :: (a -> Bool) -> Seq a -> Seq a -- | <math>. 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
--   
lookup :: Int -> Seq a -> Maybe a -- | <math>. A flipped, infix version of lookup. (!?) :: Seq a -> Int -> Maybe a -- | <math>. 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 (!?). index :: Seq a -> Int -> a -- | <math>. 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 -- | <math>. 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
--   
adjust' :: forall a. (a -> a) -> Int -> Seq a -> Seq a -- | <math>. Replace the element at the specified position. If the -- position is out of range, the original sequence is returned. update :: Int -> a -> Seq a -> Seq a -- | <math>. 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. take :: Int -> Seq a -> Seq a -- | <math>. 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. drop :: Int -> Seq a -> Seq a -- | <math>. 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
--   
insertAt :: Int -> a -> Seq a -> Seq a -- | <math>. 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]
--   
deleteAt :: Int -> Seq a -> Seq a -- | <math>. Split a sequence at a given position. splitAt -- i s = (take i s, drop i s). splitAt :: Int -> Seq a -> (Seq a, Seq a) -- | elemIndexL finds the leftmost index of the specified element, -- if it is present, and otherwise Nothing. elemIndexL :: Eq a => a -> Seq a -> Maybe Int -- | elemIndicesL finds the indices of the specified element, from -- left to right (i.e. in ascending order). elemIndicesL :: Eq a => a -> Seq a -> [Int] -- | elemIndexR finds the rightmost index of the specified element, -- if it is present, and otherwise Nothing. elemIndexR :: Eq a => a -> Seq a -> Maybe Int -- | elemIndicesR finds the indices of the specified element, from -- right to left (i.e. in descending order). elemIndicesR :: Eq a => a -> Seq a -> [Int] -- | findIndexL p xs finds the index of the leftmost -- element that satisfies p, if any exist. findIndexL :: (a -> Bool) -> Seq a -> Maybe Int -- | findIndicesL p finds all indices of elements that -- satisfy p, in ascending order. findIndicesL :: (a -> Bool) -> Seq a -> [Int] -- | findIndexR p xs finds the index of the rightmost -- element that satisfies p, if any exist. findIndexR :: (a -> Bool) -> Seq a -> Maybe Int -- | findIndicesR p finds all indices of elements that -- satisfy p, in descending order. findIndicesR :: (a -> Bool) -> Seq a -> [Int] foldMapWithIndex :: Monoid m => (Int -> a -> m) -> Seq a -> m -- | foldlWithIndex is a version of foldl that also provides -- access to the index of each element. foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b -- | foldrWithIndex is a version of foldr that also provides -- access to the index of each element. foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b -- | 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. mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b -- | traverseWithIndex is a version of traverse that also -- offers access to the index of each element. traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) -- | <math>. The reverse of a sequence. reverse :: Seq a -> Seq a -- | <math>. 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]
--   
intersperse :: a -> Seq a -> Seq a liftA2Seq :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -- | <math>. 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. zip :: Seq a -> Seq b -> Seq (a, b) -- | <math>. 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. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -- | <math>. zip3 takes three sequences and returns a sequence -- of triples, analogous to zip. zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c) -- | <math>. 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. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -- | <math>. zip4 takes four sequences and returns a sequence -- of quadruples, analogous to zip. zip4 :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d) -- | <math>. 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. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -- | Unzip a sequence of pairs. -- --
--   unzip ps = ps `seq` (fmap fst ps) (fmap snd ps)
--   
-- -- Example: -- --
--   unzip $ fromList [(1,"a"), (2,"b"), (3,"c")] =
--     (fromList [1,2,3], fromList ["a", "b", "c"])
--   
-- -- See the note about efficiency at unzipWith. unzip :: Seq (a, b) -> (Seq a, Seq b) -- | <math>. Unzip a sequence using a function to divide elements. -- --
--   unzipWith f xs == unzip (fmap f 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. unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) instance GHC.Read.Read a => GHC.Read.Read (Data.Sequence.Internal.ViewL a) instance GHC.Show.Show a => GHC.Show.Show (Data.Sequence.Internal.ViewL a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Sequence.Internal.ViewL a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Sequence.Internal.ViewL a) instance GHC.Read.Read a => GHC.Read.Read (Data.Sequence.Internal.ViewR a) instance GHC.Show.Show a => GHC.Show.Show (Data.Sequence.Internal.ViewR a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Sequence.Internal.ViewR a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Sequence.Internal.ViewR a) instance GHC.Generics.Generic1 Data.Sequence.Internal.FingerTree instance GHC.Generics.Generic (Data.Sequence.Internal.FingerTree a) instance GHC.Generics.Generic1 Data.Sequence.Internal.Digit instance GHC.Generics.Generic (Data.Sequence.Internal.Digit a) instance GHC.Generics.Generic1 Data.Sequence.Internal.Node instance GHC.Generics.Generic (Data.Sequence.Internal.Node a) instance GHC.Generics.Generic1 Data.Sequence.Internal.Elem instance GHC.Generics.Generic (Data.Sequence.Internal.Elem a) instance Data.Data.Data a => Data.Data.Data (Data.Sequence.Internal.ViewL a) instance GHC.Generics.Generic1 Data.Sequence.Internal.ViewL instance GHC.Generics.Generic (Data.Sequence.Internal.ViewL a) instance Data.Data.Data a => Data.Data.Data (Data.Sequence.Internal.ViewR a) instance GHC.Generics.Generic1 Data.Sequence.Internal.ViewR instance GHC.Generics.Generic (Data.Sequence.Internal.ViewR a) instance Data.Sequence.Internal.UnzipWith Data.Sequence.Internal.Elem instance Data.Sequence.Internal.UnzipWith Data.Sequence.Internal.Node instance Data.Sequence.Internal.UnzipWith Data.Sequence.Internal.Digit instance Data.Sequence.Internal.UnzipWith Data.Sequence.Internal.FingerTree instance Data.Sequence.Internal.UnzipWith Data.Sequence.Internal.Seq instance GHC.Base.Functor Data.Sequence.Internal.ViewR instance Data.Foldable.Foldable Data.Sequence.Internal.ViewR instance Data.Traversable.Traversable Data.Sequence.Internal.ViewR instance Data.Data.Data a => Data.Data.Data (Data.Sequence.Internal.Seq a) instance GHC.Base.Functor Data.Sequence.Internal.ViewL instance Data.Foldable.Foldable Data.Sequence.Internal.ViewL instance Data.Traversable.Traversable Data.Sequence.Internal.ViewL instance GHC.Base.Functor Data.Sequence.Internal.Seq instance Data.Foldable.Foldable Data.Sequence.Internal.Seq instance Data.Traversable.Traversable Data.Sequence.Internal.Seq instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Sequence.Internal.Seq a) instance GHC.Base.Monad Data.Sequence.Internal.Seq instance Control.Monad.Fix.MonadFix Data.Sequence.Internal.Seq instance GHC.Base.Applicative Data.Sequence.Internal.Seq instance GHC.Base.MonadPlus Data.Sequence.Internal.Seq instance GHC.Base.Alternative Data.Sequence.Internal.Seq instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Sequence.Internal.Seq a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Sequence.Internal.Seq a) instance GHC.Show.Show a => GHC.Show.Show (Data.Sequence.Internal.Seq a) instance Data.Functor.Classes.Show1 Data.Sequence.Internal.Seq instance Data.Functor.Classes.Eq1 Data.Sequence.Internal.Seq instance Data.Functor.Classes.Ord1 Data.Sequence.Internal.Seq instance GHC.Read.Read a => GHC.Read.Read (Data.Sequence.Internal.Seq a) instance Data.Functor.Classes.Read1 Data.Sequence.Internal.Seq instance GHC.Base.Monoid (Data.Sequence.Internal.Seq a) instance GHC.Base.Semigroup (Data.Sequence.Internal.Seq a) instance GHC.Exts.IsList (Data.Sequence.Internal.Seq a) instance (a GHC.Types.~ GHC.Types.Char) => Data.String.IsString (Data.Sequence.Internal.Seq a) instance Control.Monad.Zip.MonadZip Data.Sequence.Internal.Seq instance Data.Sequence.Internal.MaybeForce (Data.Sequence.Internal.Elem a) instance Data.Sequence.Internal.Sized a => Data.Sequence.Internal.Sized (Data.Sequence.Internal.FingerTree a) instance Data.Sequence.Internal.Sized (Data.Sequence.Internal.Elem a) instance GHC.Base.Functor Data.Sequence.Internal.Elem instance Data.Foldable.Foldable Data.Sequence.Internal.Elem instance Data.Traversable.Traversable Data.Sequence.Internal.Elem instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Sequence.Internal.Elem a) instance Data.Foldable.Foldable Data.Sequence.Internal.FingerTree instance GHC.Base.Functor Data.Sequence.Internal.FingerTree instance Data.Traversable.Traversable Data.Sequence.Internal.FingerTree instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Sequence.Internal.FingerTree a) instance Data.Sequence.Internal.MaybeForce (Data.Sequence.Internal.Node a) instance Data.Foldable.Foldable Data.Sequence.Internal.Node instance GHC.Base.Functor Data.Sequence.Internal.Node instance Data.Traversable.Traversable Data.Sequence.Internal.Node instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Sequence.Internal.Node a) instance Data.Sequence.Internal.Sized (Data.Sequence.Internal.Node a) instance Data.Foldable.Foldable Data.Sequence.Internal.Digit instance GHC.Base.Functor Data.Sequence.Internal.Digit instance Data.Traversable.Traversable Data.Sequence.Internal.Digit instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Sequence.Internal.Digit a) instance Data.Sequence.Internal.Sized a => Data.Sequence.Internal.Sized (Data.Sequence.Internal.Digit a) instance Data.Sequence.Internal.MaybeForce (Data.Sequence.Internal.ForceBox a) instance Data.Sequence.Internal.Sized (Data.Sequence.Internal.ForceBox a) -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- This module provides the various sorting implementations for -- Data.Sequence. Further notes are available in the file -- sorting.md (in this directory). module Data.Sequence.Internal.Sorting -- | <math>. 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. sort :: Ord a => Seq a -> Seq a -- | <math>. sortBy sorts the specified Seq according -- to the specified comparator. The sort is stable. If stability is not -- required, unstableSortBy can be slightly faster. sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a -- | <math>. sortOn sorts the specified Seq by -- comparing the results of a key function applied to each element. -- sortOn f is equivalent to sortBy -- (compare `on` f), but has the performance advantage -- of only evaluating 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 <math> evaluations, rather -- than <math>. -- -- If f is very cheap (for example a record selector, or -- fst), sortBy (compare `on` f) -- will be faster than sortOn f. sortOn :: Ord b => (a -> b) -> Seq a -> Seq a -- | <math>. 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. unstableSort :: Ord a => Seq a -> Seq a -- | <math>. 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. unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq a -- | <math>. unstableSortOn sorts the specified Seq by -- comparing the results of a key function applied to each element. -- unstableSortOn f is equivalent to -- unstableSortBy (compare `on` f), but has -- the performance advantage of only evaluating 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 <math> evaluations, -- rather than <math>. -- -- If f is very cheap (for example a record selector, or -- fst), unstableSortBy (compare `on` -- f) will be faster than unstableSortOn f. unstableSortOn :: Ord b => (a -> b) -> Seq a -> Seq a -- | A simple pairing heap. data Queue e Q :: !e -> QList e -> Queue e data QList e Nil :: QList e QCons :: {-# UNPACK #-} !Queue e -> QList e -> QList e infixr 8 `QCons` -- | A pairing heap tagged with the original position of elements, to allow -- for stable sorting. data IndexedQueue e IQ :: {-# UNPACK #-} !Int -> !e -> IQList e -> IndexedQueue e data IQList e IQNil :: IQList e IQCons :: {-# UNPACK #-} !IndexedQueue e -> IQList e -> IQList e infixr 8 `IQCons` -- | A pairing heap tagged with some key for sorting elements, for use in -- unstableSortOn. data TaggedQueue a b TQ :: !a -> b -> TQList a b -> TaggedQueue a b data TQList a b TQNil :: TQList a b TQCons :: {-# UNPACK #-} !TaggedQueue a b -> TQList a b -> TQList a b infixr 8 `TQCons` -- | A pairing heap tagged with both a key and the original position of its -- elements, for use in sortOn. data IndexedTaggedQueue e a ITQ :: {-# UNPACK #-} !Int -> !e -> a -> ITQList e a -> IndexedTaggedQueue e a data ITQList e a ITQNil :: ITQList e a ITQCons :: {-# UNPACK #-} !IndexedTaggedQueue e a -> ITQList e a -> ITQList e a infixr 8 `ITQCons` -- | mergeQ merges two Queues. mergeQ :: (a -> a -> Ordering) -> Queue a -> Queue a -> Queue a -- | mergeIQ merges two IndexedQueues, taking into account -- the original position of the elements. mergeIQ :: (a -> a -> Ordering) -> IndexedQueue a -> IndexedQueue a -> IndexedQueue a -- | mergeTQ merges two TaggedQueues, based on the tag value. mergeTQ :: (a -> a -> Ordering) -> TaggedQueue a b -> TaggedQueue a b -> TaggedQueue a b -- | mergeITQ merges two IndexedTaggedQueues, based on the -- tag value, taking into account the original position of the elements. mergeITQ :: (a -> a -> Ordering) -> IndexedTaggedQueue a b -> IndexedTaggedQueue a b -> IndexedTaggedQueue a b -- | Pop the smallest element from the queue, using the supplied -- comparator. popMinQ :: (e -> e -> Ordering) -> Queue e -> (Queue e, e) -- | Pop the smallest element from the queue, using the supplied -- comparator, deferring to the item's original position when the -- comparator returns EQ. popMinIQ :: (e -> e -> Ordering) -> IndexedQueue e -> (IndexedQueue e, e) -- | Pop the smallest element from the queue, using the supplied comparator -- on the tag. popMinTQ :: (a -> a -> Ordering) -> TaggedQueue a b -> (TaggedQueue a b, b) -- | Pop the smallest element from the queue, using the supplied comparator -- on the tag, deferring to the item's original position when the -- comparator returns EQ. popMinITQ :: (e -> e -> Ordering) -> IndexedTaggedQueue e b -> (IndexedTaggedQueue e b, b) buildQ :: (b -> b -> Ordering) -> (a -> Queue b) -> FingerTree a -> Maybe (Queue b) buildIQ :: (b -> b -> Ordering) -> (Int -> Elem y -> IndexedQueue b) -> Int -> FingerTree (Elem y) -> Maybe (IndexedQueue b) buildTQ :: (b -> b -> Ordering) -> (a -> TaggedQueue b c) -> FingerTree a -> Maybe (TaggedQueue b c) buildITQ :: (b -> b -> Ordering) -> (Int -> Elem y -> IndexedTaggedQueue b c) -> Int -> FingerTree (Elem y) -> Maybe (IndexedTaggedQueue b c) -- | A foldMap-like function, specialized to the Option -- monoid, which takes advantage of the internal structure of Seq -- to avoid wrapping in Maybe at certain points. foldToMaybeTree :: (b -> b -> b) -> (a -> b) -> FingerTree a -> Maybe b -- | A foldMapWithIndex-like function, specialized to the -- Option monoid, which takes advantage of the internal structure -- of Seq to avoid wrapping in Maybe at certain points. foldToMaybeWithIndexTree :: (b -> b -> b) -> (Int -> Elem y -> b) -> Int -> FingerTree (Elem y) -> Maybe b -- |

Finite sequences

-- -- The Seq a type represents a finite sequence of values -- of type a. -- -- Sequences generally behave very much like lists. -- -- -- -- There are two major differences between sequences and lists: -- -- -- -- 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! -- -- -- -- 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 -- -- -- -- 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 -- -- module Data.Sequence -- | General-purpose finite sequences. data Seq a -- | A bidirectional pattern synonym matching an empty sequence. pattern Empty :: Seq a -- | A bidirectional pattern synonym viewing the front of a non-empty -- sequence. pattern (:<|) :: a -> Seq a -> Seq a -- | A bidirectional pattern synonym viewing the rear of a non-empty -- sequence. pattern (:|>) :: Seq a -> a -> Seq a infixr 5 :<| infixl 5 :|> -- | <math>. The empty sequence. empty :: Seq a -- | <math>. A singleton sequence. singleton :: a -> Seq a -- | <math>. Add an element to the left end of a sequence. Mnemonic: -- a triangle with the single element at the pointy end. (<|) :: a -> Seq a -> Seq a infixr 5 <| -- | <math>. Add an element to the right end of a sequence. Mnemonic: -- a triangle with the single element at the pointy end. (|>) :: Seq a -> a -> Seq a infixl 5 |> -- | <math>. Concatenate two sequences. (><) :: Seq a -> Seq a -> Seq a infixr 5 >< -- | <math>. 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. fromList :: [a] -> Seq a -- | <math>. Convert a given sequence length and a function -- representing that sequence into a sequence. fromFunction :: Int -> (Int -> a) -> Seq a -- | <math>. 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. fromArray :: Ix i => Array i a -> Seq a -- | <math>. replicate n x is a sequence consisting of -- n copies of x. replicate :: Int -> a -> Seq a -- | replicateA is an Applicative version of -- replicate, and makes <math> calls to liftA2 and -- pure. -- --
--   replicateA n x = sequenceA (replicate n x)
--   
replicateA :: Applicative f => Int -> f a -> f (Seq a) -- | 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. replicateM :: Applicative m => Int -> m a -> m (Seq a) -- | 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
--   
cycleTaking :: Int -> Seq a -> Seq a -- | <math>. 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))
--   
iterateN :: Int -> (a -> a) -> a -> 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. unfoldr :: (b -> Maybe (a, b)) -> b -> Seq a -- | unfoldl f x is equivalent to reverse -- (unfoldr (fmap swap . f) x). unfoldl :: (b -> Maybe (b, a)) -> b -> Seq a -- | <math>. Is this the empty sequence? null :: Seq a -> Bool -- | <math>. The number of elements in the sequence. length :: Seq a -> Int -- | View of the left end of a sequence. data ViewL a -- | empty sequence EmptyL :: ViewL a -- | leftmost element and the rest of the sequence (:<) :: a -> Seq a -> ViewL a infixr 5 :< -- | <math>. Analyse the left end of a sequence. viewl :: Seq a -> ViewL a -- | View of the right end of a sequence. data ViewR a -- | empty sequence EmptyR :: ViewR a -- | the sequence minus the rightmost element, and the rightmost element (:>) :: Seq a -> a -> ViewR a infixl 5 :> -- | <math>. Analyse the right end of a sequence. viewr :: Seq a -> ViewR a -- | 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, ...]
--   
scanl :: (a -> b -> a) -> a -> Seq b -> Seq a -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f (fromList [x1, x2, ...]) = fromList [x1, x1 `f` x2, ...]
--   
scanl1 :: (a -> a -> a) -> Seq a -> Seq a -- | scanr is the right-to-left dual of scanl. scanr :: (a -> b -> b) -> b -> Seq a -> Seq b -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (a -> a -> a) -> Seq a -> Seq a -- | <math>. 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 <math>th suffix takes <math>, but -- evaluating every suffix in the sequence takes <math> due to -- sharing. tails :: Seq a -> Seq (Seq a) -- | <math>. 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 <math>th prefix takes <math>, but -- evaluating every prefix in the sequence takes <math> due to -- sharing. inits :: Seq a -> Seq (Seq a) -- | <math>. 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 -- <math> (for <math>) to <math> (for <math>). -- The true bound is more like <math> chunksOf :: Int -> Seq a -> Seq (Seq a) -- | <math> where <math> 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. takeWhileL :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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)). takeWhileR :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> is the prefix length. -- dropWhileL p xs returns the suffix remaining after -- takeWhileL p xs. dropWhileL :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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)). dropWhileR :: (a -> Bool) -> Seq a -> Seq a -- | <math> where <math> 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. spanl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math> where <math> 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. spanr :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math> where <math> 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). breakl :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | breakr p is equivalent to spanr (not . -- p). breakr :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math>. 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. partition :: (a -> Bool) -> Seq a -> (Seq a, Seq a) -- | <math>. The filter function takes a predicate p -- and a sequence xs and returns a sequence of those elements -- which satisfy the predicate. filter :: (a -> Bool) -> Seq a -> Seq a -- | <math>. 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. sort :: Ord a => Seq a -> Seq a -- | <math>. sortBy sorts the specified Seq according -- to the specified comparator. The sort is stable. If stability is not -- required, unstableSortBy can be slightly faster. sortBy :: (a -> a -> Ordering) -> Seq a -> Seq a -- | <math>. sortOn sorts the specified Seq by -- comparing the results of a key function applied to each element. -- sortOn f is equivalent to sortBy -- (compare `on` f), but has the performance advantage -- of only evaluating 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 <math> evaluations, rather -- than <math>. -- -- If f is very cheap (for example a record selector, or -- fst), sortBy (compare `on` f) -- will be faster than sortOn f. sortOn :: Ord b => (a -> b) -> Seq a -> Seq a -- | <math>. 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. unstableSort :: Ord a => Seq a -> Seq a -- | <math>. 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. unstableSortBy :: (a -> a -> Ordering) -> Seq a -> Seq a -- | <math>. unstableSortOn sorts the specified Seq by -- comparing the results of a key function applied to each element. -- unstableSortOn f is equivalent to -- unstableSortBy (compare `on` f), but has -- the performance advantage of only evaluating 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 <math> evaluations, -- rather than <math>. -- -- If f is very cheap (for example a record selector, or -- fst), unstableSortBy (compare `on` -- f) will be faster than unstableSortOn f. unstableSortOn :: Ord b => (a -> b) -> Seq a -> Seq a -- | <math>. 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
--   
lookup :: Int -> Seq a -> Maybe a -- | <math>. A flipped, infix version of lookup. (!?) :: Seq a -> Int -> Maybe a -- | <math>. 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 (!?). index :: Seq a -> Int -> a -- | <math>. 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 -- | <math>. 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
--   
adjust' :: forall a. (a -> a) -> Int -> Seq a -> Seq a -- | <math>. Replace the element at the specified position. If the -- position is out of range, the original sequence is returned. update :: Int -> a -> Seq a -> Seq a -- | <math>. 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. take :: Int -> Seq a -> Seq a -- | <math>. 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. drop :: Int -> Seq a -> Seq a -- | <math>. 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
--   
insertAt :: Int -> a -> Seq a -> Seq a -- | <math>. 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]
--   
deleteAt :: Int -> Seq a -> Seq a -- | <math>. Split a sequence at a given position. splitAt -- i s = (take i s, drop i s). splitAt :: Int -> Seq a -> (Seq a, Seq a) -- | elemIndexL finds the leftmost index of the specified element, -- if it is present, and otherwise Nothing. elemIndexL :: Eq a => a -> Seq a -> Maybe Int -- | elemIndicesL finds the indices of the specified element, from -- left to right (i.e. in ascending order). elemIndicesL :: Eq a => a -> Seq a -> [Int] -- | elemIndexR finds the rightmost index of the specified element, -- if it is present, and otherwise Nothing. elemIndexR :: Eq a => a -> Seq a -> Maybe Int -- | elemIndicesR finds the indices of the specified element, from -- right to left (i.e. in descending order). elemIndicesR :: Eq a => a -> Seq a -> [Int] -- | findIndexL p xs finds the index of the leftmost -- element that satisfies p, if any exist. findIndexL :: (a -> Bool) -> Seq a -> Maybe Int -- | findIndicesL p finds all indices of elements that -- satisfy p, in ascending order. findIndicesL :: (a -> Bool) -> Seq a -> [Int] -- | findIndexR p xs finds the index of the rightmost -- element that satisfies p, if any exist. findIndexR :: (a -> Bool) -> Seq a -> Maybe Int -- | findIndicesR p finds all indices of elements that -- satisfy p, in descending order. findIndicesR :: (a -> Bool) -> Seq a -> [Int] foldMapWithIndex :: Monoid m => (Int -> a -> m) -> Seq a -> m -- | foldlWithIndex is a version of foldl that also provides -- access to the index of each element. foldlWithIndex :: (b -> Int -> a -> b) -> b -> Seq a -> b -- | foldrWithIndex is a version of foldr that also provides -- access to the index of each element. foldrWithIndex :: (Int -> a -> b -> b) -> b -> Seq a -> b -- | 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. mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b -- | traverseWithIndex is a version of traverse that also -- offers access to the index of each element. traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) -- | <math>. The reverse of a sequence. reverse :: Seq a -> Seq a -- | <math>. 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]
--   
intersperse :: a -> Seq a -> Seq a -- | <math>. 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. zip :: Seq a -> Seq b -> Seq (a, b) -- | <math>. 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. zipWith :: (a -> b -> c) -> Seq a -> Seq b -> Seq c -- | <math>. zip3 takes three sequences and returns a sequence -- of triples, analogous to zip. zip3 :: Seq a -> Seq b -> Seq c -> Seq (a, b, c) -- | <math>. 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. zipWith3 :: (a -> b -> c -> d) -> Seq a -> Seq b -> Seq c -> Seq d -- | <math>. zip4 takes four sequences and returns a sequence -- of quadruples, analogous to zip. zip4 :: Seq a -> Seq b -> Seq c -> Seq d -> Seq (a, b, c, d) -- | <math>. 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. zipWith4 :: (a -> b -> c -> d -> e) -> Seq a -> Seq b -> Seq c -> Seq d -> Seq e -- | Unzip a sequence of pairs. -- --
--   unzip ps = ps `seq` (fmap fst ps) (fmap snd ps)
--   
-- -- Example: -- --
--   unzip $ fromList [(1,"a"), (2,"b"), (3,"c")] =
--     (fromList [1,2,3], fromList ["a", "b", "c"])
--   
-- -- See the note about efficiency at unzipWith. unzip :: Seq (a, b) -> (Seq a, Seq b) -- | <math>. Unzip a sequence using a function to divide elements. -- --
--   unzipWith f xs == unzip (fmap f 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. unzipWith :: (a -> (b, c)) -> Seq a -> (Seq b, Seq c) -- |

Multi-way Trees and Forests

-- -- The Tree a type represents a lazy, possibly infinite, -- multi-way tree (also known as a rose tree). -- -- The Forest a type represents a forest of -- Tree as. module Data.Tree -- | Non-empty, possibly infinite, multi-way trees; also known as rose -- trees. data Tree a Node :: a -> [Tree a] -> Tree a -- | label value [rootLabel] :: Tree a -> a -- | zero or more child trees [subForest] :: Tree a -> [Tree a] -- | This type synonym exists primarily for historical reasons. type Forest a = [Tree a] -- | Build a (possibly infinite) tree from a seed value in breadth-first -- order. -- -- unfoldTree f b constructs a tree by starting with the tree -- Node { rootLabel=b, subForest=[] } and repeatedly applying -- f to each rootLabel value in the tree's leaves to -- generate its subForest. -- -- For a monadic version see unfoldTreeM_BF. -- --

Examples

-- -- Construct the tree of Integers where each node has two -- children: left = 2*x and right = 2*x + 1, where -- x is the rootLabel of the node. Stop when the values -- exceed 7. -- --
--   let buildNode x = if 2*x + 1 > 7 then (x, []) else (x, [2*x, 2*x+1])
--   putStr $ drawTree $ fmap show $ unfoldTree buildNode 1
--   
-- --
--   1
--   |
--   +- 2
--   |  |
--   |  +- 4
--   |  |
--   |  `- 5
--   |
--   `- 3
--      |
--      +- 6
--      |
--      `- 7
--   
unfoldTree :: (b -> (a, [b])) -> b -> Tree a -- | Build a (possibly infinite) forest from a list of seed values in -- breadth-first order. -- -- unfoldForest f seeds invokes unfoldTree on each seed -- value. -- -- For a monadic version see unfoldForestM_BF. unfoldForest :: (b -> (a, [b])) -> [b] -> [Tree a] -- | Monadic tree builder, in depth-first order. unfoldTreeM :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a) -- | Monadic forest builder, in depth-first order unfoldForestM :: Monad m => (b -> m (a, [b])) -> [b] -> m [Tree a] -- | Monadic tree builder, in breadth-first order. -- -- See unfoldTree for more info. -- -- Implemented using an algorithm adapted from /Breadth-First Numbering: -- Lessons from a Small Exercise in Algorithm Design, by Chris -- Okasaki, ICFP'00/. unfoldTreeM_BF :: Monad m => (b -> m (a, [b])) -> b -> m (Tree a) -- | Monadic forest builder, in breadth-first order -- -- See unfoldForest for more info. -- -- Implemented using an algorithm adapted from /Breadth-First Numbering: -- Lessons from a Small Exercise in Algorithm Design, by Chris -- Okasaki, ICFP'00/. unfoldForestM_BF :: Monad m => (b -> m (a, [b])) -> [b] -> m [Tree a] -- | Fold a tree into a "summary" value in depth-first order. -- -- For each node in the tree, apply f to the rootLabel -- and the result of applying f to each subForest. -- -- This is also known as the catamorphism on trees. -- --

Examples

-- -- Sum the values in a tree: -- --
--   foldTree (\x xs -> sum (x:xs)) (Node 1 [Node 2 [], Node 3 []]) == 6
--   
-- -- Find the maximum value in the tree: -- --
--   foldTree (\x xs -> maximum (x:xs)) (Node 1 [Node 2 [], Node 3 []]) == 3
--   
-- -- Count the number of leaves in the tree: -- --
--   foldTree (\_ xs -> if null xs then 1 else sum xs) (Node 1 [Node 2 [], Node 3 []]) == 2
--   
-- -- Find depth of the tree; i.e. the number of branches from the root of -- the tree to the furthest leaf: -- --
--   foldTree (\_ xs -> if null xs then 0 else 1 + maximum xs) (Node 1 [Node 2 [], Node 3 []]) == 1
--   
-- -- You can even implement traverse using foldTree: -- --
--   traverse' f = foldTree (\x xs -> liftA2 Node (f x) (sequenceA xs))
--   
foldTree :: (a -> [b] -> b) -> Tree a -> b -- | Returns the elements of a tree in pre-order. -- --
--     a
--    / \    => [a,b,c]
--   b   c
--   
-- --

Examples

-- --
--   flatten (Node 1 [Node 2 [], Node 3 []]) == [1,2,3]
--   
flatten :: Tree a -> [a] -- | Returns the list of nodes at each level of the tree. -- --
--     a
--    / \    => [[a], [b,c]]
--   b   c
--   
-- --

Examples

-- --
--   levels (Node 1 [Node 2 [], Node 3 []]) == [[1],[2,3]]
--   
levels :: Tree a -> [[a]] -- | 2-dimensional ASCII drawing of a tree. -- --

Examples

-- --
--   putStr $ drawTree $ fmap show (Node 1 [Node 2 [], Node 3 []])
--   
-- --
--   1
--   |
--   +- 2
--   |
--   `- 3
--   
drawTree :: Tree String -> String -- | 2-dimensional ASCII drawing of a forest. -- --

Examples

-- --
--   putStr $ drawForest $ map (fmap show) [(Node 1 [Node 2 [], Node 3 []]), (Node 10 [Node 20 []])]
--   
-- --
--   1
--   |
--   +- 2
--   |
--   `- 3
--   
--   10
--   |
--   `- 20
--   
drawForest :: [Tree String] -> String instance GHC.Generics.Generic1 Data.Tree.Tree instance GHC.Generics.Generic (Data.Tree.Tree a) instance Data.Data.Data a => Data.Data.Data (Data.Tree.Tree a) instance GHC.Show.Show a => GHC.Show.Show (Data.Tree.Tree a) instance GHC.Read.Read a => GHC.Read.Read (Data.Tree.Tree a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.Tree.Tree a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.Tree.Tree a) instance Data.Functor.Classes.Eq1 Data.Tree.Tree instance Data.Functor.Classes.Ord1 Data.Tree.Tree instance Data.Functor.Classes.Show1 Data.Tree.Tree instance Data.Functor.Classes.Read1 Data.Tree.Tree instance GHC.Base.Functor Data.Tree.Tree instance GHC.Base.Applicative Data.Tree.Tree instance GHC.Base.Monad Data.Tree.Tree instance Control.Monad.Fix.MonadFix Data.Tree.Tree instance Data.Traversable.Traversable Data.Tree.Tree instance Data.Foldable.Foldable Data.Tree.Tree instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Tree.Tree a) instance Control.Monad.Zip.MonadZip Data.Tree.Tree -- |

Finite Graphs

-- -- The Graph type is an adjacency list representation of -- a finite, directed graph with vertices of type Int. -- -- The SCC type represents a strongly-connected -- component of a graph. -- --

Implementation

-- -- The implementation is based on -- -- module Data.Graph -- | Adjacency list representation of a graph, mapping each vertex to its -- list of successors. type Graph = Array Vertex [Vertex] -- | The bounds of an Array. type Bounds = (Vertex, Vertex) -- | An edge from the first vertex to the second. type Edge = (Vertex, Vertex) -- | Abstract representation of vertices. type Vertex = Int -- | Table indexed by a contiguous set of vertices. -- -- Note: This is included for backwards compatibility. type Table a = Array Vertex a -- | Build a graph from a list of nodes uniquely identified by keys, with a -- list of keys of nodes this node should have edges to. -- -- This function takes an adjacency list representing a graph with -- vertices of type key labeled by values of type node -- and produces a Graph-based representation of that list. The -- Graph result represents the shape of the graph, and -- the functions describe a) how to retrieve the label and adjacent -- vertices of a given vertex, and b) how to retrieve a vertex given a -- key. -- --
--   (graph, nodeFromVertex, vertexFromKey) = graphFromEdges edgeList
--   
-- -- -- -- To safely use this API you must either extract the list of vertices -- directly from the graph or first call vertexFromKey k to -- check if a vertex corresponds to the key k. Once it is known -- that a vertex exists you can use nodeFromVertex to access the -- labelled node and adjacent vertices. See below for examples. -- -- Note: The out-list may contain keys that don't correspond to nodes of -- the graph; they are ignored. -- -- Warning: The nodeFromVertex function will cause a runtime -- exception if the given Vertex does not exist. -- --

Examples

-- -- An empty graph. -- --
--   (graph, nodeFromVertex, vertexFromKey) = graphFromEdges []
--   graph = array (0,-1) []
--   
-- -- A graph where the out-list references unspecified nodes -- ('c'), these are ignored. -- --
--   (graph, _, _) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c'])]
--   array (0,1) [(0,[1]),(1,[])]
--   
-- -- A graph with 3 vertices: ("a") -> ("b") -> ("c") -- --
--   (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
--   graph == array (0,2) [(0,[1]),(1,[2]),(2,[])]
--   nodeFromVertex 0 == ("a",'a',"b")
--   vertexFromKey 'a' == Just 0
--   
-- -- Get the label for a given key. -- --
--   let getNodePart (n, _, _) = n
--   (graph, nodeFromVertex, vertexFromKey) = graphFromEdges [("a", 'a', ['b']), ("b", 'b', ['c']), ("c", 'c', [])]
--   getNodePart . nodeFromVertex <$> vertexFromKey 'a' == Just "A"
--   
graphFromEdges :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key]), key -> Maybe Vertex) -- | Identical to graphFromEdges, except that the return value does -- not include the function which maps keys to vertices. This version of -- graphFromEdges is for backwards compatibility. graphFromEdges' :: Ord key => [(node, key, [key])] -> (Graph, Vertex -> (node, key, [key])) -- | Build a graph from a list of edges. -- -- Warning: This function will cause a runtime exception if a vertex in -- the edge list is not within the given Bounds. -- --

Examples

-- --
--   buildG (0,-1) [] == array (0,-1) []
--   buildG (0,2) [(0,1), (1,2)] == array (0,1) [(0,[1]),(1,[2])]
--   buildG (0,2) [(0,1), (0,2), (1,2)] == array (0,2) [(0,[2,1]),(1,[2]),(2,[])]
--   
buildG :: Bounds -> [Edge] -> Graph -- | Returns the list of vertices in the graph. -- --

Examples

-- --
--   vertices (buildG (0,-1) []) == []
--   
-- --
--   vertices (buildG (0,2) [(0,1),(1,2)]) == [0,1,2]
--   
vertices :: Graph -> [Vertex] -- | Returns the list of edges in the graph. -- --

Examples

-- --
--   edges (buildG (0,-1) []) == []
--   
-- --
--   edges (buildG (0,2) [(0,1),(1,2)]) == [(0,1),(1,2)]
--   
edges :: Graph -> [Edge] -- | A table of the count of edges from each node. -- --

Examples

-- --
--   outdegree (buildG (0,-1) []) == array (0,-1) []
--   
-- --
--   outdegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,1),(1,1),(2,0)]
--   
outdegree :: Graph -> Array Vertex Int -- | A table of the count of edges into each node. -- --

Examples

-- --
--   indegree (buildG (0,-1) []) == array (0,-1) []
--   
-- --
--   indegree (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,0),(1,1),(2,1)]
--   
indegree :: Graph -> Array Vertex Int -- | The graph obtained by reversing all edges. -- --

Examples

-- --
--   transposeG (buildG (0,2) [(0,1), (1,2)]) == array (0,2) [(0,[]),(1,[0]),(2,[1])]
--   
transposeG :: Graph -> Graph -- | A spanning forest of the part of the graph reachable from the listed -- vertices, obtained from a depth-first search of the graph starting at -- each of the listed vertices in order. dfs :: Graph -> [Vertex] -> Forest Vertex -- | A spanning forest of the graph, obtained from a depth-first search of -- the graph starting from each vertex in an unspecified order. dff :: Graph -> Forest Vertex -- | A topological sort of the graph. The order is partially specified by -- the condition that a vertex i precedes j whenever -- j is reachable from i but not vice versa. topSort :: Graph -> [Vertex] -- | Reverse ordering of topSort. reverseTopSort :: Graph -> [Vertex] -- | The connected components of a graph. Two vertices are connected if -- there is a path between them, traversing edges in either direction. components :: Graph -> Forest Vertex -- | The strongly connected components of a graph, in reverse topological -- order. -- --

Examples

-- --
--   scc (buildG (0,3) [(3,1),(1,2),(2,0),(0,1)])
--     == [Node {rootLabel = 0, subForest = [Node {rootLabel = 1, subForest = [Node {rootLabel = 2, subForest = []}]}]}
--        ,Node {rootLabel = 3, subForest = []}]
--   
scc :: Graph -> Forest Vertex -- | The biconnected components of a graph. An undirected graph is -- biconnected if the deletion of any vertex leaves it connected. bcc :: Graph -> Forest [Vertex] -- | Returns the list of vertices reachable from a given vertex. -- --

Examples

-- --
--   reachable (buildG (0,0) []) 0 == [0]
--   
-- --
--   reachable (buildG (0,2) [(0,1), (1,2)]) 0 == [0,1,2]
--   
reachable :: Graph -> Vertex -> [Vertex] -- | Returns True if the second vertex reachable from the first. -- --

Examples

-- --
--   path (buildG (0,0) []) 0 0 == True
--   
-- --
--   path (buildG (0,2) [(0,1), (1,2)]) 0 2 == True
--   
-- --
--   path (buildG (0,2) [(0,1), (1,2)]) 2 0 == False
--   
path :: Graph -> Vertex -> Vertex -> Bool -- | Strongly connected component. data SCC vertex -- | A single vertex that is not in any cycle. AcyclicSCC :: vertex -> SCC vertex -- | A maximal set of mutually reachable vertices. CyclicSCC :: [vertex] -> SCC vertex -- | The strongly connected components of a directed graph, reverse -- topologically sorted. -- --

Examples

-- --
--   stronglyConnComp [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
--     == [CyclicSCC ["d"],CyclicSCC ["b","c"],AcyclicSCC "a"]
--   
stronglyConnComp :: Ord key => [(node, key, [key])] -> [SCC node] -- | The strongly connected components of a directed graph, reverse -- topologically sorted. The function is the same as -- stronglyConnComp, except that all the information about each -- node retained. This interface is used when you expect to apply -- SCC to (some of) the result of SCC, so you don't want to -- lose the dependency information. -- --

Examples

-- --
--   stronglyConnCompR [("a",0,[1]),("b",1,[2,3]),("c",2,[1]),("d",3,[3])]
--    == [CyclicSCC [("d",3,[3])],CyclicSCC [("b",1,[2,3]),("c",2,[1])],AcyclicSCC ("a",0,[1])]
--   
stronglyConnCompR :: Ord key => [(node, key, [key])] -> [SCC (node, key, [key])] -- | The vertices of a strongly connected component. flattenSCC :: SCC vertex -> [vertex] -- | The vertices of a list of strongly connected components. flattenSCCs :: [SCC a] -> [a] -- | This type synonym exists primarily for historical reasons. type Forest a = [Tree a] -- | Non-empty, possibly infinite, multi-way trees; also known as rose -- trees. data Tree a Node :: a -> [Tree a] -> Tree a instance GHC.Read.Read vertex => GHC.Read.Read (Data.Graph.SCC vertex) instance GHC.Show.Show vertex => GHC.Show.Show (Data.Graph.SCC vertex) instance GHC.Classes.Eq vertex => GHC.Classes.Eq (Data.Graph.SCC vertex) instance Data.Data.Data vertex => Data.Data.Data (Data.Graph.SCC vertex) instance GHC.Generics.Generic1 Data.Graph.SCC instance GHC.Generics.Generic (Data.Graph.SCC vertex) instance GHC.Base.Monad (Data.Graph.SetM s) instance GHC.Base.Functor (Data.Graph.SetM s) instance GHC.Base.Applicative (Data.Graph.SetM s) instance Data.Functor.Classes.Eq1 Data.Graph.SCC instance Data.Functor.Classes.Show1 Data.Graph.SCC instance Data.Functor.Classes.Read1 Data.Graph.SCC instance Data.Foldable.Foldable Data.Graph.SCC instance Data.Traversable.Traversable Data.Graph.SCC instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.Graph.SCC a) instance GHC.Base.Functor Data.Graph.SCC -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- An efficient implementation of maps from keys to values -- (dictionaries). -- -- Since many function names (but not the type name) clash with -- Prelude names, this module is usually imported -- qualified, e.g. -- --
--   import Data.Map (Map)
--   import qualified Data.Map as Map
--   
-- -- The implementation of Map is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- -- -- Note that the implementation is left-biased -- the elements of -- a first argument are always preferred to the second, for example in -- union or insert. -- -- Operation comments contain the operation time complexity in the Big-O -- notation http://en.wikipedia.org/wiki/Big_O_notation. module Data.Map.Internal -- | A Map from keys k to values a. -- -- The Semigroup operation for Map is union, which -- prefers values from the left operand. If m1 maps a key -- k to a value a1, and m2 maps the same key -- to a different value a2, then their union m1 <> -- m2 maps k to a1. data Map k a Bin :: {-# UNPACK #-} !Size -> !k -> a -> !Map k a -> !Map k a -> Map k a Tip :: Map k a type Size = Int -- | O(log n). Find the value at a key. Calls error when the -- element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: Ord k => Map k a -> k -> a infixl 9 ! -- | O(log n). Find the value at a key. Returns Nothing when -- the element can not be found. -- --
--   fromList [(5, 'a'), (3, 'b')] !? 1 == Nothing
--   
-- --
--   fromList [(5, 'a'), (3, 'b')] !? 5 == Just 'a'
--   
(!?) :: Ord k => Map k a -> k -> Maybe a infixl 9 !? -- | Same as difference. (\\) :: Ord k => Map k a -> Map k b -> Map k a infixl 9 \\ -- | O(1). Is the map empty? -- --
--   Data.Map.null (empty)           == True
--   Data.Map.null (singleton 1 'a') == False
--   
null :: Map k a -> Bool -- | O(1). The number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: Map k a -> Int -- | O(log n). Is the key a member of the map? See also -- notMember. -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Ord k => k -> Map k a -> Bool -- | O(log n). Is the key not a member of the map? See also -- member. -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Ord k => k -> Map k a -> Bool -- | O(log n). Lookup the value at a key in the map. -- -- The function will return the corresponding value as (Just -- value), or Nothing if the key isn't in the map. -- -- An example of using lookup: -- --
--   import Prelude hiding (lookup)
--   import Data.Map
--   
--   employeeDept = fromList([("John","Sales"), ("Bob","IT")])
--   deptCountry = fromList([("IT","USA"), ("Sales","France")])
--   countryCurrency = fromList([("USA", "Dollar"), ("France", "Euro")])
--   
--   employeeCurrency :: String -> Maybe String
--   employeeCurrency name = do
--       dept <- lookup name employeeDept
--       country <- lookup dept deptCountry
--       lookup country countryCurrency
--   
--   main = do
--       putStrLn $ "John's currency: " ++ (show (employeeCurrency "John"))
--       putStrLn $ "Pete's currency: " ++ (show (employeeCurrency "Pete"))
--   
-- -- The output of this program: -- --
--   John's currency: Just "Euro"
--   Pete's currency: Nothing
--   
lookup :: Ord k => k -> Map k a -> Maybe a -- | O(log n). The expression (findWithDefault def k -- map) returns the value at key k or returns default value -- def when the key is not in the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: Ord k => a -> k -> Map k a -> a -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: Map k a -- | O(1). A map with a single element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: k -> a -> Map k a -- | O(log n). Insert a new key and value in the map. If the key is -- already present in the map, the associated value is replaced with the -- supplied value. insert is equivalent to insertWith -- const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Ord k => k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining new value and old -- value. insertWith f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert the pair (key, f -- new_value old_value). -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining key, new value and -- old value. insertWithKey f key value mp will insert -- the pair (key, value) into mp if key does not exist in the -- map. If the key does exist, the function will insert the pair -- (key,f key new_value old_value). Note that the key passed to -- f is the same key passed to insertWithKey. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Combines insert operation with old value retrieval. -- The expression (insertLookupWithKey f k x map) is a -- pair where the first element is equal to (lookup k -- map) and the second element equal to (insertWithKey f -- k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) -- | O(log n). Delete a key and its value from the map. When the key -- is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Ord k => k -> Map k a -> Map k a -- | O(log n). Update a value at a specific key with the result of -- the provided function. When the key is not a member of the map, the -- original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a -- | O(log n). Adjust a value at a specific key. When the key is not -- a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a -- | O(log n). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (updateWithKey f k -- map) updates the value x at k (if it is in the -- map). If (f k x) is Nothing, the element is deleted. -- If it is (Just y), the key k is bound to the -- new value y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). Lookup and update. See also updateWithKey. The -- function returns changed value, if it is updated. Returns the original -- key value if the map entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "5:new a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) -- | O(log n). The expression (alter f k map) alters -- the value x at k, or absence thereof. alter -- can be used to insert, delete, or update a value in a Map. In -- short : lookup k (alter f k m) = f (lookup k -- m). -- --
--   let f _ = Nothing
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
--   let f _ = Just "c"
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "c")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "c")]
--   
-- -- Note that adjust = alter . fmap. alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in a Map. In short: lookup k <$> -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> Map Int String -> IO (Map Int String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. When used with -- trivial functors like Identity and Const, it is often -- slightly slower than more specialized combinators like lookup -- and insert. However, when the functor is non-trivial and key -- comparison is not particularly cheap, it is the fastest way. -- -- Note on rewrite rules: -- -- This module includes GHC rewrite rules to optimize alterF for -- the Const and Identity functors. In general, these rules -- improve performance. The sole exception is that when using -- Identity, deleting a key that is already absent takes longer -- than it would without the rules. If you expect this to occur a very -- large fraction of the time, you might consider using a private copy of -- the Identity type. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: (Functor f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a) -- | O(m*log(n/m + 1)), m <= n. The expression (union -- t1 t2) takes the left-biased union of t1 and -- t2. It prefers t1 when duplicate keys are -- encountered, i.e. (union == unionWith -- const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: Ord k => Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a -- | The union of a list of maps: (unions == foldl -- union empty). -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: (Foldable f, Ord k) => f (Map k a) -> Map k a -- | The union of a list of maps, with a combining operation: -- (unionsWith f == foldl (unionWith f) -- empty). -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: (Foldable f, Ord k) => (a -> a -> a) -> f (Map k a) -> Map k a -- | O(m*log(n/m + 1)), m <= n. Difference of two maps. Return -- elements of the first map not existing in the second map. -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: Ord k => Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the values -- of these keys. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection of two maps. Return -- data in the first map for the keys existing in both maps. -- (intersection m1 m2 == intersectionWith const -- m1 m2). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: Ord k => Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Check whether the key sets of two -- maps are disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord k => Map k a -> Map k b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.Map.Strict exposed a version -- of compose that forced the values of the output Map. -- This version does not force these values. compose :: Ord b => Map b c -> Map a b -> Map a c -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing k x z is an abstract -- representation of a function of type k -> x -> Maybe z -- . type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched k x y z is an abstract -- representation of a function of type k -> x -> y -> -- Maybe z . type SimpleWhenMatched = WhenMatched Identity -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f k x y z and k -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f k x y and k -> x -> f (Maybe y). runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y) -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge preserveMissing dropMissing (zipWithMatched f)
--   
-- --
--   symmetricDifference = merge preserveMissing preserveMissing (zipWithMaybeMatched $ \ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (mapMissing f) (mapMissing g) (zipWithMatched h)
--   
merge :: Ord k => SimpleWhenMissing k a c -> SimpleWhenMissing k b c -> SimpleWhenMatched k a b c -> Map k a -> Map k b -> Map k c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched :: (k -> x -> y -> Maybe z)
--                       -> SimpleWhenMatched k x y z
--   
zipWithMaybeMatched :: Applicative f => (k -> x -> y -> Maybe z) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched :: (k -> x -> y -> z)
--                  -> SimpleWhenMatched k x y z
--   
zipWithMatched :: Applicative f => (k -> x -> y -> z) -> WhenMatched f k x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (k -> x -> Maybe y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (k -> x -> Maybe y) -> WhenMissing f k x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing k x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f k x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f k x x -- | Force the entries whose keys are missing from the other map and -- otherwise preserve them unchanged. -- --
--   preserveMissing' :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing' = Merge.Lazy.mapMaybeMissing (\_ x -> Just $! x)
--   
-- -- but preserveMissing' is quite a bit faster. preserveMissing' :: Applicative f => WhenMissing f k x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (k -> x -> y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing k x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (k -> x -> Bool) -> WhenMissing f k x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type k -> x -> f (Maybe z) -- . data WhenMissing f k x y WhenMissing :: (Map k x -> f (Map k y)) -> (k -> x -> f (Maybe y)) -> WhenMissing f k x y [missingSubtree] :: WhenMissing f k x y -> Map k x -> f (Map k y) [missingKey] :: WhenMissing f k x y -> k -> x -> f (Maybe y) -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f k x y z is an abstract -- representation of a function of type k -> x -> y -> f -- (Maybe z) . newtype WhenMatched f k x y z WhenMatched :: (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z [matchedKey] :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: (Applicative f, Ord k) => WhenMissing f k a c -> WhenMissing f k b c -> WhenMatched f k a b c -> Map k a -> Map k b -> f (Map k c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (k -> x -> y -> f z) -> WhenMatched f k x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (k -> x -> f (Maybe y)) -> WhenMissing f k x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (k -> x -> f y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     k x -> (b -> guard b *> Just x) $ f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (k -> x -> f Bool) -> WhenMissing f k x x -- | O(n+m). An unsafe general combining function. -- -- WARNING: This function can produce corrupt maps and its results may -- depend on the internal structures of its inputs. Users should prefer -- merge or mergeA. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two Maps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f, -- filterWithKey f, or mapMaybeWithKey f -- could be used for any f. mergeWithKey :: Ord k => (k -> a -> b -> Maybe c) -> (Map k a -> Map k c) -> (Map k b -> Map k c) -> Map k a -> Map k b -> Map k c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> Map k a -> Map k b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b -- | O(n). traverseWithKey f m == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b) -- | O(n). The function mapAccum threads an accumulating -- argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n*log n). mapKeys f s is the map obtained by -- applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. The value at the greater of the two -- original keys is used as the first argument to c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). mapKeysMonotonic f s == mapKeys f -- s, but works only when f is strictly monotonic. That is, -- for any values x and y, if x < -- y then f x < f y. The precondition is -- not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   valid (mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")])) == True
--   valid (mapKeysMonotonic (\ _ -> 1)     (fromList [(5,"a"), (3,"b")])) == False
--   
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: Map k a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: Map k a -> [k] -- | O(n). An alias for toAscList. Return all key/value pairs -- in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: Map k a -> [(k, a)] -- | O(n). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.Set.fromList [3,5]
--   keysSet empty == Data.Set.empty
--   
keysSet :: Map k a -> Set k -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.Set.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.Set.empty == empty
--   
fromSet :: (k -> a) -> Set k -> Map k a -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: Map k a -> [(k, a)] -- | O(n*log n). Build a map from a list of key/value pairs. See -- also fromAscList. If the list contains more than one value for -- the same key, the last value for the key is retained. -- -- If the keys of the list are ordered, linear-time implementation is -- used, with the performance equal to fromDistinctAscList. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: Ord k => [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWithKey. -- --
--   let f k a1 a2 = (show k) ++ a1 ++ a2
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "3ab"), (5, "5a5ba")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: Map k a -> [(k, a)] -- | O(n). Build a map from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromAscList [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")]) == True
--   valid (fromAscListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctAscList [(3,"b"), (5,"a")])          == True
--   valid (fromDistinctAscList [(3,"b"), (5,"a"), (5,"b")]) == False
--   
fromDistinctAscList :: [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time. The -- precondition (input list is descending) is not checked. -- --
--   fromDescList [(5,"a"), (3,"b")]          == fromList [(3, "b"), (5, "a")]
--   fromDescList [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromDescList [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromDescListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctDescList [(5,"a"), (3,"b")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctDescList [(5,"a"), (3,"b")])          == True
--   valid (fromDistinctDescList [(5,"a"), (5,"b"), (3,"b")]) == False
--   
fromDistinctDescList :: [(k, a)] -> Map k a -- | O(n). Filter all values that satisfy the predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> Map k a -> Map k a -- | O(n). Filter all keys/values that satisfy the predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a -- | O(log n). Take while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile (p . fst) . toList
--   takeWhileAntitone p = filterWithKey (k _ -> p k)
--   
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Drop while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile (p . fst) . toList
--   dropWhileAntitone p = filterWithKey (k -> not (p k))
--   
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Divide a map at the point where a predicate on the -- keys stops holding. The user is responsible for ensuring that for all -- keys j and k in the map, j < k ==> p j -- >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partitionWithKey (k _ -> p k) xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the map at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first key and to fail after -- the last key). spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(m*log(n/m + 1)), m <= n. Restrict a Map to only -- those keys found in a Set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   m `restrictKeys` s = m `intersection` fromSet (const ()) s
--   
restrictKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(m*log(n/m + 1)), m <= n. Remove all keys in a Set -- from a Map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   m `withoutKeys` s = m `difference` fromSet (const ()) s
--   
withoutKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(log n). The expression (split k map) is a -- pair (map1,map2) where the keys in map1 are smaller -- than k and the keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Ord k => k -> Map k a -> (Map k a, Map k a) -- | O(log n). The expression (splitLookup k map) -- splits a map just like split but also returns lookup -- k map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d')],fromList [(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Map k b -> [Map k b] -- | O(m*log(n/m + 1)), m <= n. This function is defined as -- (isSubmapOf = isSubmapOfBy (==)). isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. The expression -- (isSubmapOfBy f t1 t2) returns True if all keys -- in t1 are in tree t2, and when f returns -- True when applied to their respective values. For example, the -- following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<=) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1),('b',2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [('a',2)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<)  (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1)])
--   
-- -- Note that isSubmapOfBy (_ _ -> True) m1 m2 tests whether -- all the keys in m1 are also keys in m2. isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). Defined as (isProperSubmapOf = -- isProperSubmapOfBy (==)). isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). The expression (isProperSubmapOfBy f -- m1 m2) returns True when keys m1 and keys -- m2 are not equal, all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(log n). Lookup the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- --
--   isJust (lookupIndex 2 (fromList [(5,"a"), (3,"b")]))   == False
--   fromJust (lookupIndex 3 (fromList [(5,"a"), (3,"b")])) == 0
--   fromJust (lookupIndex 5 (fromList [(5,"a"), (3,"b")])) == 1
--   isJust (lookupIndex 6 (fromList [(5,"a"), (3,"b")]))   == False
--   
lookupIndex :: Ord k => k -> Map k a -> Maybe Int -- | O(log n). Return the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- Calls error when the key is not a member of the map. -- --
--   findIndex 2 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   findIndex 3 (fromList [(5,"a"), (3,"b")]) == 0
--   findIndex 5 (fromList [(5,"a"), (3,"b")]) == 1
--   findIndex 6 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   
findIndex :: Ord k => k -> Map k a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   elemAt 0 (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   elemAt 1 (fromList [(5,"a"), (3,"b")]) == (5, "a")
--   elemAt 2 (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
elemAt :: Int -> Map k a -> (k, a) -- | O(log n). Update the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   updateAt (\ _ _ -> Just "x") 0    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "x"), (5, "a")]
--   updateAt (\ _ _ -> Just "x") 1    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "x")]
--   updateAt (\ _ _ -> Just "x") 2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\ _ _ -> Just "x") (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  0    (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   updateAt (\_ _  -> Nothing)  1    (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   updateAt (\_ _  -> Nothing)  2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   deleteAt 0  (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   deleteAt 1  (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   deleteAt 2 (fromList [(5,"a"), (3,"b")])     Error: index out of range
--   deleteAt (-1) (fromList [(5,"a"), (3,"b")])  Error: index out of range
--   
deleteAt :: Int -> Map k a -> Map k a -- | Take a given number of entries in key order, beginning with the -- smallest keys. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Map k a -> Map k a -- | Drop a given number of entries in key order, beginning with the -- smallest keys. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Map k a -> Map k a -- | O(log n). Split a map at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Map k a -> (Map k a, Map k a) -- | O(log n). The minimal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMin (fromList [(5,"a"), (3,"b")]) == Just (3,"b")
--   lookupMin empty = Nothing
--   
lookupMin :: Map k a -> Maybe (k, a) -- | O(log n). The maximal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMax (fromList [(5,"a"), (3,"b")]) == Just (5,"a")
--   lookupMax empty = Nothing
--   
lookupMax :: Map k a -> Maybe (k, a) -- | O(log n). The minimal key of the map. Calls error if the -- map is empty. -- --
--   findMin (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   findMin empty                            Error: empty map has no minimal element
--   
findMin :: Map k a -> (k, a) findMax :: Map k a -> (k, a) -- | O(log n). Delete the minimal key. Returns an empty map if the -- map is empty. -- --
--   deleteMin (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(5,"a"), (7,"c")]
--   deleteMin empty == empty
--   
deleteMin :: Map k a -> Map k a -- | O(log n). Delete the maximal key. Returns an empty map if the -- map is empty. -- --
--   deleteMax (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(3,"b"), (5,"a")]
--   deleteMax empty == empty
--   
deleteMax :: Map k a -> Map k a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((3,"b"), fromList[(5,"a"), (10,"c")])
--   deleteFindMin empty                                      Error: can not return the minimal element of an empty map
--   
deleteFindMin :: Map k a -> ((k, a), Map k a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((10,"c"), fromList [(3,"b"), (5,"a")])
--   deleteFindMax empty                                      Error: can not return the maximal element of an empty map
--   
deleteFindMax :: Map k a -> ((k, a), Map k a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Retrieves the value associated with minimal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   minView (fromList [(5,"a"), (3,"b")]) == Just ("b", singleton 5 "a")
--   minView empty == Nothing
--   
minView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the value associated with maximal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b")
--   maxView empty == Nothing
--   
maxView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | O(log n). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a) data AreWeStrict Strict :: AreWeStrict Lazy :: AreWeStrict atKeyImpl :: (Functor f, Ord k) => AreWeStrict -> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a) atKeyPlain :: Ord k => AreWeStrict -> k -> (Maybe a -> Maybe a) -> Map k a -> Map k a bin :: k -> a -> Map k a -> Map k a -> Map k a balance :: k -> a -> Map k a -> Map k a -> Map k a balanceL :: k -> a -> Map k a -> Map k a -> Map k a balanceR :: k -> a -> Map k a -> Map k a -> Map k a delta :: Int insertMax :: k -> a -> Map k a -> Map k a link :: k -> a -> Map k a -> Map k a -> Map k a link2 :: Map k a -> Map k a -> Map k a glue :: Map k a -> Map k a -> Map k a data MaybeS a NothingS :: MaybeS a JustS :: !a -> MaybeS a -- | Identity functor and monad. (a non-strict monad) newtype Identity a Identity :: a -> Identity a [runIdentity] :: Identity a -> a -- | Map covariantly over a WhenMissing f k x. mapWhenMissing :: (Applicative f, Monad f) => (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b -- | Map covariantly over a WhenMatched f k x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b -- | Map contravariantly over a WhenMissing f k _ x. lmapWhenMissing :: (b -> a) -> WhenMissing f k a x -> WhenMissing f k b x -- | Map contravariantly over a WhenMatched f k _ y z. contramapFirstWhenMatched :: (b -> a) -> WhenMatched f k a y z -> WhenMatched f k b y z -- | Map contravariantly over a WhenMatched f k x _ z. contramapSecondWhenMatched :: (b -> a) -> WhenMatched f k x a z -> WhenMatched f k x b z -- | Map covariantly over a WhenMissing f k x, using only a -- 'Functor f' constraint. mapGentlyWhenMissing :: Functor f => (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b -- | Map covariantly over a WhenMatched f k x, using only a -- 'Functor f' constraint. mapGentlyWhenMatched :: Functor f => (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b instance GHC.Base.Functor f => GHC.Base.Functor (Data.Map.Internal.WhenMatched f k x y) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => Control.Category.Category (Data.Map.Internal.WhenMatched f k x) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => GHC.Base.Applicative (Data.Map.Internal.WhenMatched f k x y) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => GHC.Base.Monad (Data.Map.Internal.WhenMatched f k x y) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Functor (Data.Map.Internal.WhenMissing f k x) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => Control.Category.Category (Data.Map.Internal.WhenMissing f k) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Applicative (Data.Map.Internal.WhenMissing f k x) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Monad (Data.Map.Internal.WhenMissing f k x) instance GHC.Classes.Ord k => GHC.Base.Monoid (Data.Map.Internal.Map k v) instance GHC.Classes.Ord k => GHC.Base.Semigroup (Data.Map.Internal.Map k v) instance (Data.Data.Data k, Data.Data.Data a, GHC.Classes.Ord k) => Data.Data.Data (Data.Map.Internal.Map k a) instance GHC.Classes.Ord k => GHC.Exts.IsList (Data.Map.Internal.Map k v) instance (GHC.Classes.Eq k, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Map.Internal.Map k a) instance (GHC.Classes.Ord k, GHC.Classes.Ord v) => GHC.Classes.Ord (Data.Map.Internal.Map k v) instance Data.Functor.Classes.Eq2 Data.Map.Internal.Map instance GHC.Classes.Eq k => Data.Functor.Classes.Eq1 (Data.Map.Internal.Map k) instance Data.Functor.Classes.Ord2 Data.Map.Internal.Map instance GHC.Classes.Ord k => Data.Functor.Classes.Ord1 (Data.Map.Internal.Map k) instance Data.Functor.Classes.Show2 Data.Map.Internal.Map instance GHC.Show.Show k => Data.Functor.Classes.Show1 (Data.Map.Internal.Map k) instance (GHC.Classes.Ord k, GHC.Read.Read k) => Data.Functor.Classes.Read1 (Data.Map.Internal.Map k) instance GHC.Base.Functor (Data.Map.Internal.Map k) instance Data.Traversable.Traversable (Data.Map.Internal.Map k) instance Data.Foldable.Foldable (Data.Map.Internal.Map k) instance Data.Bifoldable.Bifoldable Data.Map.Internal.Map instance (Control.DeepSeq.NFData k, Control.DeepSeq.NFData a) => Control.DeepSeq.NFData (Data.Map.Internal.Map k a) instance (GHC.Classes.Ord k, GHC.Read.Read k, GHC.Read.Read e) => GHC.Read.Read (Data.Map.Internal.Map k e) instance (GHC.Show.Show k, GHC.Show.Show a) => GHC.Show.Show (Data.Map.Internal.Map k a) -- | This module defines an API for writing functions that merge two maps. -- The key functions are merge and mergeA. Each of these -- can be used with several different "merge tactics". -- -- The merge and mergeA functions are shared by the lazy -- and strict modules. Only the choice of merge tactics determines -- strictness. If you use mapMissing from -- Data.Map.Merge.Strict then the results will be forced before -- they are inserted. If you use mapMissing from this module then -- they will not. -- --

Efficiency note

-- -- The Category, Applicative, and Monad instances -- for WhenMissing tactics are included because they are valid. -- However, they are inefficient in many cases and should usually be -- avoided. The instances for WhenMatched tactics should not pose -- any major efficiency problems. module Data.Map.Merge.Lazy -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing k x z is an abstract -- representation of a function of type k -> x -> Maybe z -- . type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched k x y z is an abstract -- representation of a function of type k -> x -> y -> -- Maybe z . type SimpleWhenMatched = WhenMatched Identity -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge preserveMissing dropMissing (zipWithMatched f)
--   
-- --
--   symmetricDifference = merge preserveMissing preserveMissing (zipWithMaybeMatched $ \ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (mapMissing f) (mapMissing g) (zipWithMatched h)
--   
merge :: Ord k => SimpleWhenMissing k a c -> SimpleWhenMissing k b c -> SimpleWhenMatched k a b c -> Map k a -> Map k b -> Map k c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched :: (k -> x -> y -> Maybe z)
--                       -> SimpleWhenMatched k x y z
--   
zipWithMaybeMatched :: Applicative f => (k -> x -> y -> Maybe z) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched :: (k -> x -> y -> z)
--                  -> SimpleWhenMatched k x y z
--   
zipWithMatched :: Applicative f => (k -> x -> y -> z) -> WhenMatched f k x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (k -> x -> Maybe y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (k -> x -> Maybe y) -> WhenMissing f k x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing k x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f k x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f k x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (k -> x -> y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing k x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (k -> x -> Bool) -> WhenMissing f k x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type k -> x -> f (Maybe z) -- . data WhenMissing f k x y -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f k x y z is an abstract -- representation of a function of type k -> x -> y -> f -- (Maybe z) . data WhenMatched f k x y z -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: (Applicative f, Ord k) => WhenMissing f k a c -> WhenMissing f k b c -> WhenMatched f k a b c -> Map k a -> Map k b -> f (Map k c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (k -> x -> y -> f z) -> WhenMatched f k x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (k -> x -> f (Maybe y)) -> WhenMissing f k x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (k -> x -> f y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     k x -> (b -> guard b *> Just x) $ f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (k -> x -> f Bool) -> WhenMissing f k x x -- | Map covariantly over a WhenMissing f k x. mapWhenMissing :: (Applicative f, Monad f) => (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b -- | Map covariantly over a WhenMatched f k x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b -- | Map contravariantly over a WhenMissing f k _ x. lmapWhenMissing :: (b -> a) -> WhenMissing f k a x -> WhenMissing f k b x -- | Map contravariantly over a WhenMatched f k _ y z. contramapFirstWhenMatched :: (b -> a) -> WhenMatched f k a y z -> WhenMatched f k b y z -- | Map contravariantly over a WhenMatched f k x _ z. contramapSecondWhenMatched :: (b -> a) -> WhenMatched f k x a z -> WhenMatched f k x b z -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f k x y z and k -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f k x y and k -> x -> f (Maybe y). runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y) module Data.Map.Internal.Debug -- | O(n). Show the tree that implements the map. The tree is shown -- in a compressed, hanging format. See showTreeWith. showTree :: (Show k, Show a) => Map k a -> String -- | O(n). The expression (showTreeWith showelem hang -- wide map) shows the tree that implements the map. Elements are -- shown using the showElem function. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. -- --
--   Map> let t = fromDistinctAscList [(x,()) | x <- [1..5]]
--   Map> putStrLn $ showTreeWith (\k x -> show (k,x)) True False t
--   (4,())
--   +--(2,())
--   |  +--(1,())
--   |  +--(3,())
--   +--(5,())
--   
--   Map> putStrLn $ showTreeWith (\k x -> show (k,x)) True True t
--   (4,())
--   |
--   +--(2,())
--   |  |
--   |  +--(1,())
--   |  |
--   |  +--(3,())
--   |
--   +--(5,())
--   
--   Map> putStrLn $ showTreeWith (\k x -> show (k,x)) False True t
--   +--(5,())
--   |
--   (4,())
--   |
--   |  +--(3,())
--   |  |
--   +--(2,())
--      |
--      +--(1,())
--   
showTreeWith :: (k -> a -> String) -> Bool -> Bool -> Map k a -> String showsTree :: (k -> a -> String) -> Bool -> [String] -> [String] -> Map k a -> ShowS showsTreeHang :: (k -> a -> String) -> Bool -> [String] -> Map k a -> ShowS showWide :: Bool -> [String] -> String -> String showsBars :: [String] -> ShowS node :: String withBar :: [String] -> [String] withEmpty :: [String] -> [String] -- | O(n). Test if the internal map structure is valid. -- --
--   valid (fromAscList [(3,"b"), (5,"a")]) == True
--   valid (fromAscList [(5,"a"), (3,"b")]) == False
--   
valid :: Ord k => Map k a -> Bool -- | Test if the keys are ordered correctly. ordered :: Ord a => Map a b -> Bool -- | Test if a map obeys the balance invariants. balanced :: Map k a -> Bool -- | Test if each node of a map reports its size correctly. validsize :: Map a b -> Bool -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- An efficient implementation of integer sets. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import Data.IntSet (IntSet)
--   import qualified Data.IntSet as IntSet
--   
-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. However, my benchmarks show that -- it is also (much) faster on insertions and deletions when compared to -- a generic size-balanced set implementation (see Data.Set). -- -- -- -- Additionally, this implementation places bitmaps in the leaves of the -- tree. Their size is the natural size of a machine word (32 or 64 bits) -- and greatly reduce memory footprint and execution times for dense -- sets, e.g. sets where it is likely that many values lie close to each -- other. The asymptotics are not affected by this optimization. -- -- Many operations have a worst-case complexity of O(min(n,W)). -- This means that the operation can become linear in the number of -- elements with a maximum of W -- the number of bits in an -- Int (32 or 64). module Data.IntSet.Internal -- | A set of integers. data IntSet Bin :: {-# UNPACK #-} !Prefix -> {-# UNPACK #-} !Mask -> !IntSet -> !IntSet -> IntSet Tip :: {-# UNPACK #-} !Prefix -> {-# UNPACK #-} !BitMap -> IntSet Nil :: IntSet type Key = Int type Prefix = Int type Mask = Int type BitMap = Word -- | O(n+m). See difference. (\\) :: IntSet -> IntSet -> IntSet infixl 9 \\ -- | O(1). Is the set empty? null :: IntSet -> Bool -- | O(n). Cardinality of the set. size :: IntSet -> Int -- | O(min(n,W)). Is the value a member of the set? member :: Key -> IntSet -> Bool -- | O(min(n,W)). Is the element not in the set? notMember :: Key -> IntSet -> Bool -- | O(log n). Find largest element smaller than the given one. -- --
--   lookupLT 3 (fromList [3, 5]) == Nothing
--   lookupLT 5 (fromList [3, 5]) == Just 3
--   
lookupLT :: Key -> IntSet -> Maybe Key -- | O(log n). Find smallest element greater than the given one. -- --
--   lookupGT 4 (fromList [3, 5]) == Just 5
--   lookupGT 5 (fromList [3, 5]) == Nothing
--   
lookupGT :: Key -> IntSet -> Maybe Key -- | O(log n). Find largest element smaller or equal to the given -- one. -- --
--   lookupLE 2 (fromList [3, 5]) == Nothing
--   lookupLE 4 (fromList [3, 5]) == Just 3
--   lookupLE 5 (fromList [3, 5]) == Just 5
--   
lookupLE :: Key -> IntSet -> Maybe Key -- | O(log n). Find smallest element greater or equal to the given -- one. -- --
--   lookupGE 3 (fromList [3, 5]) == Just 3
--   lookupGE 4 (fromList [3, 5]) == Just 5
--   lookupGE 6 (fromList [3, 5]) == Nothing
--   
lookupGE :: Key -> IntSet -> Maybe Key -- | O(n+m). Is this a subset? (s1 `isSubsetOf` s2) tells -- whether s1 is a subset of s2. isSubsetOf :: IntSet -> IntSet -> Bool -- | O(n+m). Is this a proper subset? (ie. a subset but not equal). isProperSubsetOf :: IntSet -> IntSet -> Bool -- | O(n+m). Check whether two sets are disjoint (i.e. their -- intersection is empty). -- --
--   disjoint (fromList [2,4,6])   (fromList [1,3])     == True
--   disjoint (fromList [2,4,6,8]) (fromList [2,3,5,7]) == False
--   disjoint (fromList [1,2])     (fromList [1,2,3,4]) == False
--   disjoint (fromList [])        (fromList [])        == True
--   
disjoint :: IntSet -> IntSet -> Bool -- | O(1). The empty set. empty :: IntSet -- | O(1). A set of one element. singleton :: Key -> IntSet -- | O(min(n,W)). Add a value to the set. There is no left- or right -- bias for IntSets. insert :: Key -> IntSet -> IntSet -- | O(min(n,W)). Delete a value in the set. Returns the original -- set when the value was not present. delete :: Key -> IntSet -> IntSet -- | O(min(n,W)). (alterF f x s) can delete or -- insert x in s depending on whether it is already -- present in s. -- -- In short: -- --
--   member x <$> alterF f x s = f (member x s)
--   
-- -- Note: alterF is a variant of the at combinator from -- Control.Lens.At. alterF :: Functor f => (Bool -> f Bool) -> Key -> IntSet -> f IntSet -- | O(n+m). The union of two sets. union :: IntSet -> IntSet -> IntSet -- | The union of a list of sets. unions :: Foldable f => f IntSet -> IntSet -- | O(n+m). Difference between two sets. difference :: IntSet -> IntSet -> IntSet -- | O(n+m). The intersection of two sets. intersection :: IntSet -> IntSet -> IntSet -- | O(n). Filter all elements that satisfy some predicate. filter :: (Key -> Bool) -> IntSet -> IntSet -- | O(n). partition the set according to some predicate. partition :: (Key -> Bool) -> IntSet -> (IntSet, IntSet) -- | O(min(n,W)). The expression (split x set) is a -- pair (set1,set2) where set1 comprises the elements -- of set less than x and set2 comprises the -- elements of set greater than x. -- --
--   split 3 (fromList [1..5]) == (fromList [1,2], fromList [4,5])
--   
split :: Key -> IntSet -> (IntSet, IntSet) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot element was found in the original set. splitMember :: Key -> IntSet -> (IntSet, Bool, IntSet) -- | O(1). Decompose a set into pieces based on the structure of the -- underlying tree. This function is useful for consuming a set in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList [1..120]) == [fromList [1..63],fromList [64..120]]
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- subsets, but you should not depend on this behaviour because it can -- change in the future without notice. Also, the current version does -- not continue splitting all the way to individual singleton sets -- it -- stops at some point. splitRoot :: IntSet -> [IntSet] -- | O(n*min(n,W)). map f s is the set obtained by -- applying f to each element of s. -- -- It's worth noting that the size of the result may be smaller if, for -- some (x,y), x /= y && f x == f y map :: (Key -> Key) -> IntSet -> IntSet -- | O(n). The -- -- mapMonotonic f s == map f s, but works only -- when f is strictly increasing. The precondition is not -- checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapMonotonic f s == map f s
--       where ls = toList s
--   
mapMonotonic :: (Key -> Key) -> IntSet -> IntSet -- | O(n). Fold the elements in the set using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . toAscList. -- -- For example, -- --
--   toAscList set = foldr (:) [] set
--   
foldr :: (Key -> b -> b) -> b -> IntSet -> b -- | O(n). Fold the elements in the set using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . toAscList. -- -- For example, -- --
--   toDescList set = foldl (flip (:)) [] set
--   
foldl :: (a -> Key -> a) -> a -> IntSet -> a -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (Key -> b -> b) -> b -> IntSet -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> Key -> a) -> a -> IntSet -> a -- | O(n). Fold the elements in the set using the given -- right-associative binary operator. This function is an equivalent of -- foldr and is present for compatibility only. -- -- Please note that fold will be deprecated in the future and -- removed. fold :: (Key -> b -> b) -> b -> IntSet -> b -- | O(min(n,W)). The minimal element of the set. findMin :: IntSet -> Key -- | O(min(n,W)). The maximal element of a set. findMax :: IntSet -> Key -- | O(min(n,W)). Delete the minimal element. Returns an empty set -- if the set is empty. -- -- Note that this is a change of behaviour for consistency with -- Set – versions prior to 0.5 threw an error if the IntSet -- was already empty. deleteMin :: IntSet -> IntSet -- | O(min(n,W)). Delete the maximal element. Returns an empty set -- if the set is empty. -- -- Note that this is a change of behaviour for consistency with -- Set – versions prior to 0.5 threw an error if the IntSet -- was already empty. deleteMax :: IntSet -> IntSet -- | O(min(n,W)). Delete and find the minimal element. -- --
--   deleteFindMin set = (findMin set, deleteMin set)
--   
deleteFindMin :: IntSet -> (Key, IntSet) -- | O(min(n,W)). Delete and find the maximal element. -- --
--   deleteFindMax set = (findMax set, deleteMax set)
--   
deleteFindMax :: IntSet -> (Key, IntSet) -- | O(min(n,W)). Retrieves the maximal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. maxView :: IntSet -> Maybe (Key, IntSet) -- | O(min(n,W)). Retrieves the minimal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. minView :: IntSet -> Maybe (Key, IntSet) -- | O(n). An alias of toAscList. The elements of a set in -- ascending order. Subject to list fusion. elems :: IntSet -> [Key] -- | O(n). Convert the set to a list of elements. Subject to list -- fusion. toList :: IntSet -> [Key] -- | O(n*min(n,W)). Create a set from a list of integers. fromList :: [Key] -> IntSet -- | O(n). Convert the set to an ascending list of elements. Subject -- to list fusion. toAscList :: IntSet -> [Key] -- | O(n). Convert the set to a descending list of elements. Subject -- to list fusion. toDescList :: IntSet -> [Key] -- | O(n). Build a set from an ascending list of elements. The -- precondition (input list is ascending) is not checked. fromAscList :: [Key] -> IntSet -- | O(n). Build a set from an ascending list of distinct elements. -- The precondition (input list is strictly ascending) is not -- checked. fromDistinctAscList :: [Key] -> IntSet -- | O(n). Show the tree that implements the set. The tree is shown -- in a compressed, hanging format. showTree :: IntSet -> String -- | O(n). The expression (showTreeWith hang wide -- map) shows the tree that implements the set. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. showTreeWith :: Bool -> Bool -> IntSet -> String match :: Int -> Prefix -> Mask -> Bool suffixBitMask :: Int prefixBitMask :: Int bitmapOf :: Int -> BitMap zero :: Int -> Mask -> Bool instance GHC.Exts.IsList Data.IntSet.Internal.IntSet instance GHC.Base.Monoid Data.IntSet.Internal.IntSet instance GHC.Base.Semigroup Data.IntSet.Internal.IntSet instance Data.Data.Data Data.IntSet.Internal.IntSet instance GHC.Classes.Eq Data.IntSet.Internal.IntSet instance GHC.Classes.Ord Data.IntSet.Internal.IntSet instance GHC.Show.Show Data.IntSet.Internal.IntSet instance GHC.Read.Read Data.IntSet.Internal.IntSet instance Control.DeepSeq.NFData Data.IntSet.Internal.IntSet -- |

Finite Int Sets

-- -- The IntSet type represents a set of elements of type -- Int. -- -- For a walkthrough of the most commonly used functions see their -- sets introduction. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import Data.IntSet (IntSet)
--   import qualified Data.IntSet as IntSet
--   
-- --

Performance information

-- -- Many operations have a worst-case complexity of O(min(n,W)). -- This means that the operation can become linear in the number of -- elements with a maximum of W -- the number of bits in an -- Int (32 or 64). -- --

Implementation

-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. However, my benchmarks show that -- it is also (much) faster on insertions and deletions when compared to -- a generic size-balanced set implementation (see Data.Set). -- -- -- -- Additionally, this implementation places bitmaps in the leaves of the -- tree. Their size is the natural size of a machine word (32 or 64 bits) -- and greatly reduces the memory footprint and execution times for dense -- sets, e.g. sets where it is likely that many values lie close to each -- other. The asymptotics are not affected by this optimization. module Data.IntSet -- | A set of integers. data IntSet type Key = Int -- | O(1). The empty set. empty :: IntSet -- | O(1). A set of one element. singleton :: Key -> IntSet -- | O(n*min(n,W)). Create a set from a list of integers. fromList :: [Key] -> IntSet -- | O(n). Build a set from an ascending list of elements. The -- precondition (input list is ascending) is not checked. fromAscList :: [Key] -> IntSet -- | O(n). Build a set from an ascending list of distinct elements. -- The precondition (input list is strictly ascending) is not -- checked. fromDistinctAscList :: [Key] -> IntSet -- | O(min(n,W)). Add a value to the set. There is no left- or right -- bias for IntSets. insert :: Key -> IntSet -> IntSet -- | O(min(n,W)). Delete a value in the set. Returns the original -- set when the value was not present. delete :: Key -> IntSet -> IntSet -- | O(min(n,W)). (alterF f x s) can delete or -- insert x in s depending on whether it is already -- present in s. -- -- In short: -- --
--   member x <$> alterF f x s = f (member x s)
--   
-- -- Note: alterF is a variant of the at combinator from -- Control.Lens.At. alterF :: Functor f => (Bool -> f Bool) -> Key -> IntSet -> f IntSet -- | O(min(n,W)). Is the value a member of the set? member :: Key -> IntSet -> Bool -- | O(min(n,W)). Is the element not in the set? notMember :: Key -> IntSet -> Bool -- | O(log n). Find largest element smaller than the given one. -- --
--   lookupLT 3 (fromList [3, 5]) == Nothing
--   lookupLT 5 (fromList [3, 5]) == Just 3
--   
lookupLT :: Key -> IntSet -> Maybe Key -- | O(log n). Find smallest element greater than the given one. -- --
--   lookupGT 4 (fromList [3, 5]) == Just 5
--   lookupGT 5 (fromList [3, 5]) == Nothing
--   
lookupGT :: Key -> IntSet -> Maybe Key -- | O(log n). Find largest element smaller or equal to the given -- one. -- --
--   lookupLE 2 (fromList [3, 5]) == Nothing
--   lookupLE 4 (fromList [3, 5]) == Just 3
--   lookupLE 5 (fromList [3, 5]) == Just 5
--   
lookupLE :: Key -> IntSet -> Maybe Key -- | O(log n). Find smallest element greater or equal to the given -- one. -- --
--   lookupGE 3 (fromList [3, 5]) == Just 3
--   lookupGE 4 (fromList [3, 5]) == Just 5
--   lookupGE 6 (fromList [3, 5]) == Nothing
--   
lookupGE :: Key -> IntSet -> Maybe Key -- | O(1). Is the set empty? null :: IntSet -> Bool -- | O(n). Cardinality of the set. size :: IntSet -> Int -- | O(n+m). Is this a subset? (s1 `isSubsetOf` s2) tells -- whether s1 is a subset of s2. isSubsetOf :: IntSet -> IntSet -> Bool -- | O(n+m). Is this a proper subset? (ie. a subset but not equal). isProperSubsetOf :: IntSet -> IntSet -> Bool -- | O(n+m). Check whether two sets are disjoint (i.e. their -- intersection is empty). -- --
--   disjoint (fromList [2,4,6])   (fromList [1,3])     == True
--   disjoint (fromList [2,4,6,8]) (fromList [2,3,5,7]) == False
--   disjoint (fromList [1,2])     (fromList [1,2,3,4]) == False
--   disjoint (fromList [])        (fromList [])        == True
--   
disjoint :: IntSet -> IntSet -> Bool -- | O(n+m). The union of two sets. union :: IntSet -> IntSet -> IntSet -- | The union of a list of sets. unions :: Foldable f => f IntSet -> IntSet -- | O(n+m). Difference between two sets. difference :: IntSet -> IntSet -> IntSet -- | O(n+m). See difference. (\\) :: IntSet -> IntSet -> IntSet infixl 9 \\ -- | O(n+m). The intersection of two sets. intersection :: IntSet -> IntSet -> IntSet -- | O(n). Filter all elements that satisfy some predicate. filter :: (Key -> Bool) -> IntSet -> IntSet -- | O(n). partition the set according to some predicate. partition :: (Key -> Bool) -> IntSet -> (IntSet, IntSet) -- | O(min(n,W)). The expression (split x set) is a -- pair (set1,set2) where set1 comprises the elements -- of set less than x and set2 comprises the -- elements of set greater than x. -- --
--   split 3 (fromList [1..5]) == (fromList [1,2], fromList [4,5])
--   
split :: Key -> IntSet -> (IntSet, IntSet) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot element was found in the original set. splitMember :: Key -> IntSet -> (IntSet, Bool, IntSet) -- | O(1). Decompose a set into pieces based on the structure of the -- underlying tree. This function is useful for consuming a set in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList [1..120]) == [fromList [1..63],fromList [64..120]]
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- subsets, but you should not depend on this behaviour because it can -- change in the future without notice. Also, the current version does -- not continue splitting all the way to individual singleton sets -- it -- stops at some point. splitRoot :: IntSet -> [IntSet] -- | O(n*min(n,W)). map f s is the set obtained by -- applying f to each element of s. -- -- It's worth noting that the size of the result may be smaller if, for -- some (x,y), x /= y && f x == f y map :: (Key -> Key) -> IntSet -> IntSet -- | O(n). The -- -- mapMonotonic f s == map f s, but works only -- when f is strictly increasing. The precondition is not -- checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapMonotonic f s == map f s
--       where ls = toList s
--   
mapMonotonic :: (Key -> Key) -> IntSet -> IntSet -- | O(n). Fold the elements in the set using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . toAscList. -- -- For example, -- --
--   toAscList set = foldr (:) [] set
--   
foldr :: (Key -> b -> b) -> b -> IntSet -> b -- | O(n). Fold the elements in the set using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . toAscList. -- -- For example, -- --
--   toDescList set = foldl (flip (:)) [] set
--   
foldl :: (a -> Key -> a) -> a -> IntSet -> a -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (Key -> b -> b) -> b -> IntSet -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> Key -> a) -> a -> IntSet -> a -- | O(n). Fold the elements in the set using the given -- right-associative binary operator. This function is an equivalent of -- foldr and is present for compatibility only. -- -- Please note that fold will be deprecated in the future and -- removed. fold :: (Key -> b -> b) -> b -> IntSet -> b -- | O(min(n,W)). The minimal element of the set. findMin :: IntSet -> Key -- | O(min(n,W)). The maximal element of a set. findMax :: IntSet -> Key -- | O(min(n,W)). Delete the minimal element. Returns an empty set -- if the set is empty. -- -- Note that this is a change of behaviour for consistency with -- Set – versions prior to 0.5 threw an error if the IntSet -- was already empty. deleteMin :: IntSet -> IntSet -- | O(min(n,W)). Delete the maximal element. Returns an empty set -- if the set is empty. -- -- Note that this is a change of behaviour for consistency with -- Set – versions prior to 0.5 threw an error if the IntSet -- was already empty. deleteMax :: IntSet -> IntSet -- | O(min(n,W)). Delete and find the minimal element. -- --
--   deleteFindMin set = (findMin set, deleteMin set)
--   
deleteFindMin :: IntSet -> (Key, IntSet) -- | O(min(n,W)). Delete and find the maximal element. -- --
--   deleteFindMax set = (findMax set, deleteMax set)
--   
deleteFindMax :: IntSet -> (Key, IntSet) -- | O(min(n,W)). Retrieves the maximal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. maxView :: IntSet -> Maybe (Key, IntSet) -- | O(min(n,W)). Retrieves the minimal key of the set, and the set -- stripped of that element, or Nothing if passed an empty set. minView :: IntSet -> Maybe (Key, IntSet) -- | O(n). An alias of toAscList. The elements of a set in -- ascending order. Subject to list fusion. elems :: IntSet -> [Key] -- | O(n). Convert the set to a list of elements. Subject to list -- fusion. toList :: IntSet -> [Key] -- | O(n). Convert the set to an ascending list of elements. Subject -- to list fusion. toAscList :: IntSet -> [Key] -- | O(n). Convert the set to a descending list of elements. Subject -- to list fusion. toDescList :: IntSet -> [Key] -- | O(n). Show the tree that implements the set. The tree is shown -- in a compressed, hanging format. showTree :: IntSet -> String -- | O(n). The expression (showTreeWith hang wide -- map) shows the tree that implements the set. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. showTreeWith :: Bool -> Bool -> IntSet -> String -- | This module provides efficient containers-based functions on the list -- type. -- -- In the documentation, <math> is the number of elements in the -- list while <math> is the number of distinct elements in the -- list. <math> is the number of bits in an Int. module Data.Containers.ListUtils -- | <math>. The nubOrd function removes duplicate elements -- from a list. In particular, it keeps only the first occurrence of each -- element. By using a Set internally it has better asymptotics -- than the standard nub function. -- --

Strictness

-- -- nubOrd is strict in the elements of the list. -- --

Efficiency note

-- -- When applicable, it is almost always better to use nubInt or -- nubIntOn instead of this function, although it can be a little -- worse in certain pathological cases. For example, to nub a list of -- characters, use -- --
--   nubIntOn fromEnum xs
--   
nubOrd :: Ord a => [a] -> [a] -- | The nubOrdOn function behaves just like nubOrd except -- it performs comparisons not on the original datatype, but a -- user-specified projection from that datatype. -- --

Strictness

-- -- nubOrdOn is strict in the values of the function applied to -- the elements of the list. nubOrdOn :: Ord b => (a -> b) -> [a] -> [a] -- | <math>. The nubInt function removes duplicate -- Int values from a list. In particular, it keeps only the first -- occurrence of each element. By using an IntSet internally, it -- attains better asymptotics than the standard nub function. -- -- See also nubIntOn, a more widely applicable generalization. -- --

Strictness

-- -- nubInt is strict in the elements of the list. nubInt :: [Int] -> [Int] -- | The nubIntOn function behaves just like nubInt except -- it performs comparisons not on the original datatype, but a -- user-specified projection from that datatype. For example, -- nubIntOn fromEnum can be used to nub characters and -- typical fixed-with numerical types efficiently. -- --

Strictness

-- -- nubIntOn is strict in the values of the function applied to -- the elements of the list. nubIntOn :: (a -> Int) -> [a] -> [a] -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- This defines the data structures and core (hidden) manipulations on -- representations. module Data.IntMap.Internal -- | A map of integers to values a. data IntMap a Bin :: {-# UNPACK #-} !Prefix -> {-# UNPACK #-} !Mask -> !IntMap a -> !IntMap a -> IntMap a Tip :: {-# UNPACK #-} !Key -> a -> IntMap a Nil :: IntMap a type Key = Int -- | O(min(n,W)). Find the value at a key. Calls error when -- the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: IntMap a -> Key -> a -- | O(min(n,W)). Find the value at a key. Returns Nothing -- when the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] !? 1 == Nothing
--   fromList [(5,'a'), (3,'b')] !? 5 == Just 'a'
--   
(!?) :: IntMap a -> Key -> Maybe a infixl 9 !? -- | Same as difference. (\\) :: IntMap a -> IntMap b -> IntMap a infixl 9 \\ -- | O(1). Is the map empty? -- --
--   Data.IntMap.null (empty)           == True
--   Data.IntMap.null (singleton 1 'a') == False
--   
null :: IntMap a -> Bool -- | O(n). Number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: IntMap a -> Int -- | O(min(n,W)). Is the key a member of the map? -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Key -> IntMap a -> Bool -- | O(min(n,W)). Is the key not a member of the map? -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Key -> IntMap a -> Bool -- | O(min(n,W)). Lookup the value at a key in the map. See also -- lookup. lookup :: Key -> IntMap a -> Maybe a -- | O(min(n,W)). The expression (findWithDefault def k -- map) returns the value at key k or returns def -- when the key is not an element of the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: a -> Key -> IntMap a -> a -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Key -> IntMap a -> Maybe (Key, a) -- | O(n+m). Check whether the key sets of two maps are disjoint -- (i.e. their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   disjoint a b == null (intersection a b)
--   
disjoint :: IntMap a -> IntMap b -> Bool -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: IntMap a -- | O(1). A map of one element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: Key -> a -> IntMap a -- | O(min(n,W)). Insert a new key/value pair in the map. If the key -- is already present in the map, the associated value is replaced with -- the supplied value, i.e. insert is equivalent to -- insertWith const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWith f key value mp will insert the pair (key, -- value) into mp if key does not exist in the map. If the key -- does exist, the function will insert f new_value old_value. -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWithKey f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert f key new_value -- old_value. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (insertLookupWithKey f k -- x map) is a pair where the first element is equal to -- (lookup k map) and the second element equal to -- (insertWithKey f k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). Delete a key and its value from the map. When the -- key is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f k x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Lookup and update. The function returns original -- value, if it is updated. This is different behavior than -- updateLookupWithKey. Returns the original key value if the map -- entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). The expression (alter f k map) -- alters the value x at k, or absence thereof. -- alter can be used to insert, delete, or update a value in an -- IntMap. In short : lookup k (alter f k m) = f -- (lookup k m). alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in an IntMap. In short : lookup k $ -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> IntMap String -> IO (IntMap String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a) -- | O(n+m). The (left-biased) union of two maps. It prefers the -- first map when duplicate keys are encountered, i.e. (union -- == unionWith const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | The union of a list of maps. -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: Foldable f => f (IntMap a) -> IntMap a -- | The union of a list of maps, with a combining operation. -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: Foldable f => (a -> a -> a) -> f (IntMap a) -> IntMap a -- | O(n+m). Difference between two maps (based on keys). -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: IntMap a -> IntMap b -> IntMap a -- | O(n+m). Difference with a combining function. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). The (left-biased) intersection of two maps (based on -- keys). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: IntMap a -> IntMap b -> IntMap a -- | O(n+m). The intersection with a combining function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). The intersection with a combining function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.IntMap.Strict exposed a -- version of compose that forced the values of the output -- IntMap. This version does not force these values. compose :: IntMap c -> IntMap Int -> IntMap c -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing x z is an abstract -- representation of a function of type Key -> x -> Maybe -- z. type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched x y z is an abstract -- representation of a function of type Key -> x -> y -> -- Maybe z. type SimpleWhenMatched = WhenMatched Identity -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f x y z and Key -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f x y and Key -> x -> f (Maybe y). runWhenMissing :: WhenMissing f x y -> Key -> x -> f (Maybe y) -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge diffPreserve diffDrop f
--   
-- --
--   symmetricDifference = merge diffPreserve diffPreserve (\ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (diffMapWithKey f) (diffMapWithKey g)
--   
merge :: SimpleWhenMissing a c -> SimpleWhenMissing b c -> SimpleWhenMatched a b c -> IntMap a -> IntMap b -> IntMap c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched
--     :: (Key -> x -> y -> Maybe z)
--     -> SimpleWhenMatched x y z
--   
zipWithMaybeMatched :: Applicative f => (Key -> x -> y -> Maybe z) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched
--     :: (Key -> x -> y -> z)
--     -> SimpleWhenMatched x y z
--   
zipWithMatched :: Applicative f => (Key -> x -> y -> z) -> WhenMatched f x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (Key -> x -> Maybe y) -> SimpleWhenMissing x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (Key -> x -> Maybe y) -> WhenMissing f x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (Key -> x -> y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (Key -> x -> Bool) -> WhenMissing f x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type Key -> x -> f (Maybe -- z). data WhenMissing f x y WhenMissing :: (IntMap x -> f (IntMap y)) -> (Key -> x -> f (Maybe y)) -> WhenMissing f x y [missingSubtree] :: WhenMissing f x y -> IntMap x -> f (IntMap y) [missingKey] :: WhenMissing f x y -> Key -> x -> f (Maybe y) -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f x y z is an abstract -- representation of a function of type Key -> x -> y -> f -- (Maybe z). newtype WhenMatched f x y z WhenMatched :: (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z [matchedKey] :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z) -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3,'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: Applicative f => WhenMissing f a c -> WhenMissing f b c -> WhenMatched f a b c -> IntMap a -> IntMap b -> f (IntMap c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (Key -> x -> y -> f z) -> WhenMatched f x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (Key -> x -> f (Maybe y)) -> WhenMissing f x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (Key -> x -> f y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     \k x -> (\b -> guard b *> Just x) <$> f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (Key -> x -> f Bool) -> WhenMissing f x x -- | O(n+m). A high-performance universal combining function. Using -- mergeWithKey, all combining functions can be defined without -- any loss of efficiency (with exception of union, -- difference and intersection, where sharing of some nodes -- is lost with mergeWithKey). -- -- Please make sure you know what is going on when using -- mergeWithKey, otherwise you can be surprised by unexpected code -- growth or even corruption of the data structure. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define your custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two IntMaps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: (Key -> a -> b -> Maybe c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c) -> IntMap a -> IntMap b -> IntMap c mergeWithKey' :: (Prefix -> Mask -> IntMap c -> IntMap c -> IntMap c) -> (IntMap a -> IntMap b -> IntMap c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c) -> IntMap a -> IntMap b -> IntMap c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> IntMap a -> IntMap b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b -- | O(n). traverseWithKey f s == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b) -- | O(n). The function mapAccum threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n*min(n,W)). mapKeys f s is the map obtained -- by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysMonotonic f s == -- mapKeys f s, but works only when f is strictly -- monotonic. That is, for any values x and y, if -- x < y then f x < f y. The -- precondition is not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has slightly better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   
mapKeysMonotonic :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: IntMap a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: IntMap a -> [Key] -- | O(n). An alias for toAscList. Returns all key/value -- pairs in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: IntMap a -> [(Key, a)] -- | O(n*min(n,W)). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.IntSet.fromList [3,5]
--   keysSet empty == Data.IntSet.empty
--   
keysSet :: IntMap a -> IntSet -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.IntSet.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.IntSet.empty == empty
--   
fromSet :: (Key -> a) -> IntSet -> IntMap a -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: IntMap a -> [(Key, a)] -- | O(n*min(n,W)). Create a map from a list of key/value pairs. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs with -- a combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")] == fromList [(3, "ab"), (5, "cba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Build a map from a list of key/value pairs with -- a combining function. See also fromAscListWithKey'. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")] == fromList [(3, "3:a|b"), (5, "5:c|5:b|a")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: IntMap a -> [(Key, a)] -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   
fromAscList :: [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "5:b|a")]
--   
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order and all distinct. The precondition (input -- list is strictly ascending) is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   
fromDistinctAscList :: [(Key, a)] -> IntMap a -- | O(n). Filter all values that satisfy some predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> IntMap a -> IntMap a -- | O(n). Filter all keys/values that satisfy some predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a -- | O(n+m). The restriction of a map to the keys in a set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   
restrictKeys :: IntMap a -> IntSet -> IntMap a -- | O(n+m). Remove all the keys in a given set from a map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   
withoutKeys :: IntMap a -> IntSet -> IntMap a -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(min(n,W)). The expression (split k map) is a -- pair (map1,map2) where all keys in map1 are lower -- than k and all keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Key -> IntMap a -> (IntMap a, IntMap a) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot key was found in the original map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6::Int] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d'),(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: IntMap a -> [IntMap a] -- | O(n+m). Is this a submap? Defined as (isSubmapOf = -- isSubmapOfBy (==)). isSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). The expression (isSubmapOfBy f m1 m2) -- returns True if all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [(1,2)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- Defined as (isProperSubmapOf = isProperSubmapOfBy -- (==)). isProperSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- The expression (isProperSubmapOfBy f m1 m2) returns -- True when keys m1 and keys m2 are not equal, -- all keys in m1 are in m2, and when f -- returns True when applied to their respective values. For -- example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(min(n,W)). The minimal key of the map. Returns Nothing -- if the map is empty. lookupMin :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The maximal key of the map. Returns Nothing -- if the map is empty. lookupMax :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The minimal key of the map. Calls error if -- the map is empty. Use minViewWithKey if the map may be empty. findMin :: IntMap a -> (Key, a) -- | O(min(n,W)). The maximal key of the map. Calls error if -- the map is empty. Use maxViewWithKey if the map may be empty. findMax :: IntMap a -> (Key, a) -- | O(min(n,W)). Delete the minimal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMin :: IntMap a -> IntMap a -- | O(min(n,W)). Delete the maximal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMax :: IntMap a -> IntMap a -- | O(min(n,W)). Delete and find the minimal element. This function -- throws an error if the map is empty. Use minViewWithKey if the -- map may be empty. deleteFindMin :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Delete and find the maximal element. This function -- throws an error if the map is empty. Use maxViewWithKey if the -- map may be empty. deleteFindMax :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Retrieves the minimal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. minView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the maximal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. maxView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | O(min(n,W)). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | O(n). Show the tree that implements the map. The tree is shown -- in a compressed, hanging format. showTree :: Show a => IntMap a -> String -- | O(n). The expression (showTreeWith hang wide -- map) shows the tree that implements the map. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. showTreeWith :: Show a => Bool -> Bool -> IntMap a -> String type Mask = Int type Prefix = Int type Nat = Word natFromInt :: Key -> Nat intFromNat :: Nat -> Key link :: Prefix -> IntMap a -> Prefix -> IntMap a -> IntMap a linkWithMask :: Mask -> Prefix -> IntMap a -> IntMap a -> IntMap a bin :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a binCheckLeft :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a binCheckRight :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a -- | Should this key follow the left subtree of a Bin with switching -- bit m? N.B., the answer is only valid when match i p -- m is true. zero :: Key -> Mask -> Bool -- | Does the key i differ from the prefix p before -- getting to the switching bit m? nomatch :: Key -> Prefix -> Mask -> Bool -- | Does the key i match the prefix p (up to but not -- including bit m)? match :: Key -> Prefix -> Mask -> Bool -- | The prefix of key i up to (but not including) the switching -- bit m. mask :: Key -> Mask -> Prefix -- | The prefix of key i up to (but not including) the switching -- bit m. maskW :: Nat -> Nat -> Prefix -- | Does the left switching bit specify a shorter prefix? shorter :: Mask -> Mask -> Bool -- | The first switching bit where the two prefixes disagree. branchMask :: Prefix -> Prefix -> Mask -- | Return a word where only the highest bit is set. highestBitMask :: Word -> Word -- | Map covariantly over a WhenMissing f x. mapWhenMissing :: (Applicative f, Monad f) => (a -> b) -> WhenMissing f x a -> WhenMissing f x b -- | Map covariantly over a WhenMatched f x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b -- | Map contravariantly over a WhenMissing f _ x. lmapWhenMissing :: (b -> a) -> WhenMissing f a x -> WhenMissing f b x -- | Map contravariantly over a WhenMatched f _ y z. contramapFirstWhenMatched :: (b -> a) -> WhenMatched f a y z -> WhenMatched f b y z -- | Map contravariantly over a WhenMatched f x _ z. contramapSecondWhenMatched :: (b -> a) -> WhenMatched f x a z -> WhenMatched f x b z -- | Map covariantly over a WhenMissing f x, using only a -- 'Functor f' constraint. mapGentlyWhenMissing :: Functor f => (a -> b) -> WhenMissing f x a -> WhenMissing f x b -- | Map covariantly over a WhenMatched f k x, using only a -- 'Functor f' constraint. mapGentlyWhenMatched :: Functor f => (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b instance GHC.Base.Functor f => GHC.Base.Functor (Data.IntMap.Internal.WhenMatched f x y) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => Control.Category.Category (Data.IntMap.Internal.WhenMatched f x) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => GHC.Base.Applicative (Data.IntMap.Internal.WhenMatched f x y) instance (GHC.Base.Monad f, GHC.Base.Applicative f) => GHC.Base.Monad (Data.IntMap.Internal.WhenMatched f x y) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Functor (Data.IntMap.Internal.WhenMissing f x) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => Control.Category.Category (Data.IntMap.Internal.WhenMissing f) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Applicative (Data.IntMap.Internal.WhenMissing f x) instance (GHC.Base.Applicative f, GHC.Base.Monad f) => GHC.Base.Monad (Data.IntMap.Internal.WhenMissing f x) instance GHC.Base.Monoid (Data.IntMap.Internal.IntMap a) instance GHC.Base.Semigroup (Data.IntMap.Internal.IntMap a) instance Data.Foldable.Foldable Data.IntMap.Internal.IntMap instance Data.Traversable.Traversable Data.IntMap.Internal.IntMap instance Control.DeepSeq.NFData a => Control.DeepSeq.NFData (Data.IntMap.Internal.IntMap a) instance Data.Data.Data a => Data.Data.Data (Data.IntMap.Internal.IntMap a) instance GHC.Exts.IsList (Data.IntMap.Internal.IntMap a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Data.IntMap.Internal.IntMap a) instance Data.Functor.Classes.Eq1 Data.IntMap.Internal.IntMap instance GHC.Classes.Ord a => GHC.Classes.Ord (Data.IntMap.Internal.IntMap a) instance Data.Functor.Classes.Ord1 Data.IntMap.Internal.IntMap instance GHC.Base.Functor Data.IntMap.Internal.IntMap instance GHC.Show.Show a => GHC.Show.Show (Data.IntMap.Internal.IntMap a) instance Data.Functor.Classes.Show1 Data.IntMap.Internal.IntMap instance GHC.Read.Read e => GHC.Read.Read (Data.IntMap.Internal.IntMap e) instance Data.Functor.Classes.Read1 Data.IntMap.Internal.IntMap -- | This module defines an API for writing functions that merge two maps. -- The key functions are merge and mergeA. Each of these -- can be used with several different "merge tactics". -- -- The merge and mergeA functions are shared by the lazy -- and strict modules. Only the choice of merge tactics determines -- strictness. If you use mapMissing from -- Data.Map.Merge.Strict then the results will be forced before -- they are inserted. If you use mapMissing from this module then -- they will not. -- --

Efficiency note

-- -- The Category, Applicative, and Monad instances -- for WhenMissing tactics are included because they are valid. -- However, they are inefficient in many cases and should usually be -- avoided. The instances for WhenMatched tactics should not pose -- any major efficiency problems. module Data.IntMap.Merge.Lazy -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing x z is an abstract -- representation of a function of type Key -> x -> Maybe -- z. type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched x y z is an abstract -- representation of a function of type Key -> x -> y -> -- Maybe z. type SimpleWhenMatched = WhenMatched Identity -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge diffPreserve diffDrop f
--   
-- --
--   symmetricDifference = merge diffPreserve diffPreserve (\ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (diffMapWithKey f) (diffMapWithKey g)
--   
merge :: SimpleWhenMissing a c -> SimpleWhenMissing b c -> SimpleWhenMatched a b c -> IntMap a -> IntMap b -> IntMap c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched
--     :: (Key -> x -> y -> Maybe z)
--     -> SimpleWhenMatched x y z
--   
zipWithMaybeMatched :: Applicative f => (Key -> x -> y -> Maybe z) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched
--     :: (Key -> x -> y -> z)
--     -> SimpleWhenMatched x y z
--   
zipWithMatched :: Applicative f => (Key -> x -> y -> z) -> WhenMatched f x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (Key -> x -> Maybe y) -> SimpleWhenMissing x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (Key -> x -> Maybe y) -> WhenMissing f x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (Key -> x -> y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (Key -> x -> Bool) -> WhenMissing f x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type Key -> x -> f (Maybe -- z). data WhenMissing f x y -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f x y z is an abstract -- representation of a function of type Key -> x -> y -> f -- (Maybe z). data WhenMatched f x y z -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3,'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: Applicative f => WhenMissing f a c -> WhenMissing f b c -> WhenMatched f a b c -> IntMap a -> IntMap b -> f (IntMap c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (Key -> x -> y -> f z) -> WhenMatched f x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (Key -> x -> f (Maybe y)) -> WhenMissing f x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (Key -> x -> f y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     \k x -> (\b -> guard b *> Just x) <$> f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (Key -> x -> f Bool) -> WhenMissing f x x -- | Map covariantly over a WhenMissing f x. mapWhenMissing :: (Applicative f, Monad f) => (a -> b) -> WhenMissing f x a -> WhenMissing f x b -- | Map covariantly over a WhenMatched f x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b -- | Map contravariantly over a WhenMissing f _ x. lmapWhenMissing :: (b -> a) -> WhenMissing f a x -> WhenMissing f b x -- | Map contravariantly over a WhenMatched f _ y z. contramapFirstWhenMatched :: (b -> a) -> WhenMatched f a y z -> WhenMatched f b y z -- | Map contravariantly over a WhenMatched f x _ z. contramapSecondWhenMatched :: (b -> a) -> WhenMatched f x a z -> WhenMatched f x b z -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f x y z and Key -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f x y and Key -> x -> f (Maybe y). runWhenMissing :: WhenMissing f x y -> Key -> x -> f (Maybe y) module Data.IntMap.Internal.Debug -- | O(n). Show the tree that implements the map. The tree is shown -- in a compressed, hanging format. showTree :: Show a => IntMap a -> String -- | O(n). The expression (showTreeWith hang wide -- map) shows the tree that implements the map. If hang is -- True, a hanging tree is shown otherwise a rotated tree -- is shown. If wide is True, an extra wide version is -- shown. showTreeWith :: Show a => Bool -> Bool -> IntMap a -> String -- |

WARNING

-- -- This module is considered internal. -- -- The Package Versioning Policy does not apply. -- -- The 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

-- -- An efficient implementation of ordered maps from keys to values -- (dictionaries). -- -- API of this module is strict in both the keys and the values. If you -- need value-lazy maps, use Data.Map.Lazy instead. The Map -- type is shared between the lazy and strict modules, meaning that the -- same Map value can be passed to functions in both modules -- (although that is rarely needed). -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import qualified Data.Map.Strict as Map
--   
-- -- The implementation of Map is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- -- -- Note that the implementation is left-biased -- the elements of -- a first argument are always preferred to the second, for example in -- union or insert. -- -- Warning: The size of the map must not exceed -- maxBound::Int. Violation of this condition is not detected -- and if the size limit is exceeded, its behaviour is undefined. -- -- Operation comments contain the operation time complexity in the Big-O -- notation (http://en.wikipedia.org/wiki/Big_O_notation). -- -- Be aware that the Functor, Traversable and Data -- instances are the same as for the Data.Map.Lazy module, so if -- they are used on strict maps, the resulting maps will be lazy. module Data.Map.Strict.Internal -- | A Map from keys k to values a. -- -- The Semigroup operation for Map is union, which -- prefers values from the left operand. If m1 maps a key -- k to a value a1, and m2 maps the same key -- to a different value a2, then their union m1 <> -- m2 maps k to a1. data Map k a Bin :: {-# UNPACK #-} !Size -> !k -> a -> !Map k a -> !Map k a -> Map k a Tip :: Map k a type Size = Int -- | O(log n). Find the value at a key. Calls error when the -- element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: Ord k => Map k a -> k -> a infixl 9 ! -- | O(log n). Find the value at a key. Returns Nothing when -- the element can not be found. -- --
--   fromList [(5, 'a'), (3, 'b')] !? 1 == Nothing
--   
-- --
--   fromList [(5, 'a'), (3, 'b')] !? 5 == Just 'a'
--   
(!?) :: Ord k => Map k a -> k -> Maybe a infixl 9 !? -- | Same as difference. (\\) :: Ord k => Map k a -> Map k b -> Map k a infixl 9 \\ -- | O(1). Is the map empty? -- --
--   Data.Map.null (empty)           == True
--   Data.Map.null (singleton 1 'a') == False
--   
null :: Map k a -> Bool -- | O(1). The number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: Map k a -> Int -- | O(log n). Is the key a member of the map? See also -- notMember. -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Ord k => k -> Map k a -> Bool -- | O(log n). Is the key not a member of the map? See also -- member. -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Ord k => k -> Map k a -> Bool -- | O(log n). Lookup the value at a key in the map. -- -- The function will return the corresponding value as (Just -- value), or Nothing if the key isn't in the map. -- -- An example of using lookup: -- --
--   import Prelude hiding (lookup)
--   import Data.Map
--   
--   employeeDept = fromList([("John","Sales"), ("Bob","IT")])
--   deptCountry = fromList([("IT","USA"), ("Sales","France")])
--   countryCurrency = fromList([("USA", "Dollar"), ("France", "Euro")])
--   
--   employeeCurrency :: String -> Maybe String
--   employeeCurrency name = do
--       dept <- lookup name employeeDept
--       country <- lookup dept deptCountry
--       lookup country countryCurrency
--   
--   main = do
--       putStrLn $ "John's currency: " ++ (show (employeeCurrency "John"))
--       putStrLn $ "Pete's currency: " ++ (show (employeeCurrency "Pete"))
--   
-- -- The output of this program: -- --
--   John's currency: Just "Euro"
--   Pete's currency: Nothing
--   
lookup :: Ord k => k -> Map k a -> Maybe a -- | O(log n). The expression (findWithDefault def k -- map) returns the value at key k or returns default value -- def when the key is not in the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: Ord k => a -> k -> Map k a -> a -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: Map k a -- | O(1). A map with a single element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: k -> a -> Map k a -- | O(log n). Insert a new key and value in the map. If the key is -- already present in the map, the associated value is replaced with the -- supplied value. insert is equivalent to insertWith -- const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Ord k => k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining new value and old -- value. insertWith f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert the pair (key, f -- new_value old_value). -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining key, new value and -- old value. insertWithKey f key value mp will insert -- the pair (key, value) into mp if key does not exist in the -- map. If the key does exist, the function will insert the pair -- (key,f key new_value old_value). Note that the key passed to -- f is the same key passed to insertWithKey. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Combines insert operation with old value retrieval. -- The expression (insertLookupWithKey f k x map) is a -- pair where the first element is equal to (lookup k -- map) and the second element equal to (insertWithKey f -- k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) -- | O(log n). Delete a key and its value from the map. When the key -- is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Ord k => k -> Map k a -> Map k a -- | O(log n). Update a value at a specific key with the result of -- the provided function. When the key is not a member of the map, the -- original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a -- | O(log n). Adjust a value at a specific key. When the key is not -- a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a -- | O(log n). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (updateWithKey f k -- map) updates the value x at k (if it is in the -- map). If (f k x) is Nothing, the element is deleted. -- If it is (Just y), the key k is bound to the -- new value y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). Lookup and update. See also updateWithKey. The -- function returns changed value, if it is updated. Returns the original -- key value if the map entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "5:new a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) -- | O(log n). The expression (alter f k map) alters -- the value x at k, or absence thereof. alter -- can be used to insert, delete, or update a value in a Map. In -- short : lookup k (alter f k m) = f (lookup k -- m). -- --
--   let f _ = Nothing
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
--   let f _ = Just "c"
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "c")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "c")]
--   
-- -- Note that adjust = alter . fmap. alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in a Map. In short: lookup k <$> -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> Map Int String -> IO (Map Int String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. When used with -- trivial functors like Identity and Const, it is often -- slightly slower than more specialized combinators like lookup -- and insert. However, when the functor is non-trivial and key -- comparison is not particularly cheap, it is the fastest way. -- -- Note on rewrite rules: -- -- This module includes GHC rewrite rules to optimize alterF for -- the Const and Identity functors. In general, these rules -- improve performance. The sole exception is that when using -- Identity, deleting a key that is already absent takes longer -- than it would without the rules. If you expect this to occur a very -- large fraction of the time, you might consider using a private copy of -- the Identity type. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: (Functor f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a) -- | O(m*log(n/m + 1)), m <= n. The expression (union -- t1 t2) takes the left-biased union of t1 and -- t2. It prefers t1 when duplicate keys are -- encountered, i.e. (union == unionWith -- const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: Ord k => Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a -- | The union of a list of maps: (unions == foldl -- union empty). -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: (Foldable f, Ord k) => f (Map k a) -> Map k a -- | The union of a list of maps, with a combining operation: -- (unionsWith f == foldl (unionWith f) -- empty). -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: (Foldable f, Ord k) => (a -> a -> a) -> f (Map k a) -> Map k a -- | O(m*log(n/m + 1)), m <= n. Difference of two maps. Return -- elements of the first map not existing in the second map. -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: Ord k => Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the values -- of these keys. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection of two maps. Return -- data in the first map for the keys existing in both maps. -- (intersection m1 m2 == intersectionWith const -- m1 m2). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: Ord k => Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Check whether the key sets of two -- maps are disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord k => Map k a -> Map k b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.Map.Strict exposed a version -- of compose that forced the values of the output Map. -- This version does not force these values. compose :: Ord b => Map b c -> Map a b -> Map a c -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing k x z is an abstract -- representation of a function of type k -> x -> Maybe z -- . type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched k x y z is an abstract -- representation of a function of type k -> x -> y -> -- Maybe z . type SimpleWhenMatched = WhenMatched Identity -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge preserveMissing dropMissing (zipWithMatched f)
--   
-- --
--   symmetricDifference = merge preserveMissing preserveMissing (zipWithMaybeMatched $ \ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (mapMissing f) (mapMissing g) (zipWithMatched h)
--   
merge :: Ord k => SimpleWhenMissing k a c -> SimpleWhenMissing k b c -> SimpleWhenMatched k a b c -> Map k a -> Map k b -> Map k c -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f k x y z and k -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f k x y and k -> x -> f (Maybe y). runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y) -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched :: (k -> x -> y -> Maybe z)
--                       -> SimpleWhenMatched k x y z
--   
zipWithMaybeMatched :: Applicative f => (k -> x -> y -> Maybe z) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched :: (k -> x -> y -> z)
--                  -> SimpleWhenMatched k x y z
--   
zipWithMatched :: Applicative f => (k -> x -> y -> z) -> WhenMatched f k x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (k -> x -> Maybe y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (k -> x -> Maybe y) -> WhenMissing f k x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing k x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f k x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f k x x -- | Force the entries whose keys are missing from the other map and -- otherwise preserve them unchanged. -- --
--   preserveMissing' :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing' = Merge.Lazy.mapMaybeMissing (\_ x -> Just $! x)
--   
-- -- but preserveMissing' is quite a bit faster. preserveMissing' :: Applicative f => WhenMissing f k x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (k -> x -> y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing k x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (k -> x -> Bool) -> WhenMissing f k x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type k -> x -> f (Maybe z) -- . data WhenMissing f k x y WhenMissing :: (Map k x -> f (Map k y)) -> (k -> x -> f (Maybe y)) -> WhenMissing f k x y [missingSubtree] :: WhenMissing f k x y -> Map k x -> f (Map k y) [missingKey] :: WhenMissing f k x y -> k -> x -> f (Maybe y) -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f k x y z is an abstract -- representation of a function of type k -> x -> y -> f -- (Maybe z) . newtype WhenMatched f k x y z WhenMatched :: (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z [matchedKey] :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: (Applicative f, Ord k) => WhenMissing f k a c -> WhenMissing f k b c -> WhenMatched f k a b c -> Map k a -> Map k b -> f (Map k c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: Applicative f => (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (k -> x -> y -> f z) -> WhenMatched f k x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (k -> x -> f (Maybe y)) -> WhenMissing f k x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (k -> x -> f y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     k x -> (b -> guard b *> Just x) $ f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (k -> x -> f Bool) -> WhenMissing f k x x -- | Map covariantly over a WhenMissing f k x. mapWhenMissing :: Functor f => (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b -- | Map covariantly over a WhenMatched f k x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b -- | O(n+m). An unsafe universal combining function. -- -- WARNING: This function can produce corrupt maps and its results may -- depend on the internal structures of its inputs. Users should prefer -- merge or mergeA. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two Maps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: Ord k => (k -> a -> b -> Maybe c) -> (Map k a -> Map k c) -> (Map k b -> Map k c) -> Map k a -> Map k b -> Map k c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> Map k a -> Map k b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b -- | O(n). traverseWithKey f m == fromList -- $ traverse ((k, v) -> (v' -> v' `seq` (k,v')) -- $ f k v) (toList m) That is, it behaves much like a -- regular traverse except that the traversing function also has -- access to the key associated with a value and the values are forced -- before they are installed in the result map. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b) -- | O(n). The function mapAccum threads an accumulating -- argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n*log n). mapKeys f s is the map obtained by -- applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. The value at the greater of the two -- original keys is used as the first argument to c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). mapKeysMonotonic f s == mapKeys f -- s, but works only when f is strictly monotonic. That is, -- for any values x and y, if x < -- y then f x < f y. The precondition is -- not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   valid (mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")])) == True
--   valid (mapKeysMonotonic (\ _ -> 1)     (fromList [(5,"a"), (3,"b")])) == False
--   
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: Map k a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: Map k a -> [k] -- | O(n). An alias for toAscList. Return all key/value pairs -- in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: Map k a -> [(k, a)] -- | O(n). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.Set.fromList [3,5]
--   keysSet empty == Data.Set.empty
--   
keysSet :: Map k a -> Set k -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.Set.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.Set.empty == empty
--   
fromSet :: (k -> a) -> Set k -> Map k a -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: Map k a -> [(k, a)] -- | O(n*log n). Build a map from a list of key/value pairs. See -- also fromAscList. If the list contains more than one value for -- the same key, the last value for the key is retained. -- -- If the keys of the list are ordered, linear-time implementation is -- used, with the performance equal to fromDistinctAscList. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: Ord k => [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWithKey. -- --
--   let f k a1 a2 = (show k) ++ a1 ++ a2
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "3ab"), (5, "5a5ba")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: Map k a -> [(k, a)] -- | O(n). Build a map from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromAscList [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")]) == True
--   valid (fromAscListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctAscList [(3,"b"), (5,"a")])          == True
--   valid (fromDistinctAscList [(3,"b"), (5,"a"), (5,"b")]) == False
--   
fromDistinctAscList :: [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time. The -- precondition (input list is descending) is not checked. -- --
--   fromDescList [(5,"a"), (3,"b")]          == fromList [(3, "b"), (5, "a")]
--   fromDescList [(5,"a"), (5,"b"), (3,"a")] == fromList [(3, "b"), (5, "b")]
--   valid (fromDescList [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromDescListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctDescList [(5,"a"), (3,"b")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctDescList [(5,"a"), (3,"b")])          == True
--   valid (fromDistinctDescList [(5,"a"), (3,"b"), (3,"a")]) == False
--   
fromDistinctDescList :: [(k, a)] -> Map k a -- | O(n). Filter all values that satisfy the predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> Map k a -> Map k a -- | O(n). Filter all keys/values that satisfy the predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Restrict a Map to only -- those keys found in a Set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   m `restrictKeys` s = m `intersection` fromSet (const ()) s
--   
restrictKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(m*log(n/m + 1)), m <= n. Remove all keys in a Set -- from a Map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   m `withoutKeys` s = m `difference` fromSet (const ()) s
--   
withoutKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(log n). Take while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile (p . fst) . toList
--   takeWhileAntitone p = filterWithKey (k _ -> p k)
--   
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Drop while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile (p . fst) . toList
--   dropWhileAntitone p = filterWithKey (k -> not (p k))
--   
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Divide a map at the point where a predicate on the -- keys stops holding. The user is responsible for ensuring that for all -- keys j and k in the map, j < k ==> p j -- >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partitionWithKey (k _ -> p k) xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the map at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first key and to fail after -- the last key). spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(log n). The expression (split k map) is a -- pair (map1,map2) where the keys in map1 are smaller -- than k and the keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Ord k => k -> Map k a -> (Map k a, Map k a) -- | O(log n). The expression (splitLookup k map) -- splits a map just like split but also returns lookup -- k map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d')],fromList [(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Map k b -> [Map k b] -- | O(m*log(n/m + 1)), m <= n. This function is defined as -- (isSubmapOf = isSubmapOfBy (==)). isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. The expression -- (isSubmapOfBy f t1 t2) returns True if all keys -- in t1 are in tree t2, and when f returns -- True when applied to their respective values. For example, the -- following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<=) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1),('b',2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [('a',2)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<)  (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1)])
--   
-- -- Note that isSubmapOfBy (_ _ -> True) m1 m2 tests whether -- all the keys in m1 are also keys in m2. isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). Defined as (isProperSubmapOf = -- isProperSubmapOfBy (==)). isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). The expression (isProperSubmapOfBy f -- m1 m2) returns True when keys m1 and keys -- m2 are not equal, all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(log n). Lookup the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- --
--   isJust (lookupIndex 2 (fromList [(5,"a"), (3,"b")]))   == False
--   fromJust (lookupIndex 3 (fromList [(5,"a"), (3,"b")])) == 0
--   fromJust (lookupIndex 5 (fromList [(5,"a"), (3,"b")])) == 1
--   isJust (lookupIndex 6 (fromList [(5,"a"), (3,"b")]))   == False
--   
lookupIndex :: Ord k => k -> Map k a -> Maybe Int -- | O(log n). Return the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- Calls error when the key is not a member of the map. -- --
--   findIndex 2 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   findIndex 3 (fromList [(5,"a"), (3,"b")]) == 0
--   findIndex 5 (fromList [(5,"a"), (3,"b")]) == 1
--   findIndex 6 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   
findIndex :: Ord k => k -> Map k a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   elemAt 0 (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   elemAt 1 (fromList [(5,"a"), (3,"b")]) == (5, "a")
--   elemAt 2 (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
elemAt :: Int -> Map k a -> (k, a) -- | O(log n). Update the element at index. Calls -- error when an invalid index is used. -- --
--   updateAt (\ _ _ -> Just "x") 0    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "x"), (5, "a")]
--   updateAt (\ _ _ -> Just "x") 1    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "x")]
--   updateAt (\ _ _ -> Just "x") 2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\ _ _ -> Just "x") (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  0    (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   updateAt (\_ _  -> Nothing)  1    (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   updateAt (\_ _  -> Nothing)  2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   deleteAt 0  (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   deleteAt 1  (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   deleteAt 2 (fromList [(5,"a"), (3,"b")])     Error: index out of range
--   deleteAt (-1) (fromList [(5,"a"), (3,"b")])  Error: index out of range
--   
deleteAt :: Int -> Map k a -> Map k a -- | Take a given number of entries in key order, beginning with the -- smallest keys. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Map k a -> Map k a -- | Drop a given number of entries in key order, beginning with the -- smallest keys. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Map k a -> Map k a -- | O(log n). Split a map at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Map k a -> (Map k a, Map k a) -- | O(log n). The minimal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMin (fromList [(5,"a"), (3,"b")]) == Just (3,"b")
--   lookupMin empty = Nothing
--   
lookupMin :: Map k a -> Maybe (k, a) -- | O(log n). The maximal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMax (fromList [(5,"a"), (3,"b")]) == Just (5,"a")
--   lookupMax empty = Nothing
--   
lookupMax :: Map k a -> Maybe (k, a) -- | O(log n). The minimal key of the map. Calls error if the -- map is empty. -- --
--   findMin (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   findMin empty                            Error: empty map has no minimal element
--   
findMin :: Map k a -> (k, a) findMax :: Map k a -> (k, a) -- | O(log n). Delete the minimal key. Returns an empty map if the -- map is empty. -- --
--   deleteMin (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(5,"a"), (7,"c")]
--   deleteMin empty == empty
--   
deleteMin :: Map k a -> Map k a -- | O(log n). Delete the maximal key. Returns an empty map if the -- map is empty. -- --
--   deleteMax (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(3,"b"), (5,"a")]
--   deleteMax empty == empty
--   
deleteMax :: Map k a -> Map k a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((3,"b"), fromList[(5,"a"), (10,"c")])
--   deleteFindMin empty                                      Error: can not return the minimal element of an empty map
--   
deleteFindMin :: Map k a -> ((k, a), Map k a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((10,"c"), fromList [(3,"b"), (5,"a")])
--   deleteFindMax empty                                      Error: can not return the maximal element of an empty map
--   
deleteFindMax :: Map k a -> ((k, a), Map k a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Retrieves the value associated with minimal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   minView (fromList [(5,"a"), (3,"b")]) == Just ("b", singleton 5 "a")
--   minView empty == Nothing
--   
minView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the value associated with maximal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b")
--   maxView empty == Nothing
--   
maxView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | O(log n). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | This function has moved to showTree. showTree :: Whoops "showTree has moved to Data.Map.Internal.Debug.showTree." => Map k a -> String -- | This function has moved to showTreeWith. showTreeWith :: Whoops "showTreeWith has moved to Data.Map.Internal.Debug.showTreeWith." => (k -> a -> String) -> Bool -> Bool -> Map k a -> String -- | O(n). Test if the internal map structure is valid. -- --
--   valid (fromAscList [(3,"b"), (5,"a")]) == True
--   valid (fromAscList [(5,"a"), (3,"b")]) == False
--   
valid :: Ord k => Map k a -> Bool -- |

Finite Maps (strict interface)

-- -- The Map k v type represents a finite map (sometimes -- called a dictionary) from keys of type k to values of type -- v. -- -- Each function in this module is careful to force values before -- installing them in a Map. This is usually more efficient when -- laziness is not necessary. When laziness is required, use the -- functions in Data.Map.Lazy. -- -- In particular, the functions in this module obey the following law: -- -- -- -- When deciding if this is the correct data structure to use, consider: -- -- -- -- For a walkthrough of the most commonly used functions see the maps -- introduction. -- -- This module is intended to be imported qualified, to avoid name -- clashes with Prelude functions: -- --
--   import qualified Data.Map.Strict as Map
--   
-- -- Note that the implementation is generally left-biased. -- Functions that take two maps as arguments and combine them, such as -- union and intersection, prefer the values in the first -- argument to those in the second. -- --

Detailed performance information

-- -- The amortized running time is given for each operation, with n -- referring to the number of entries in the map. -- -- Benchmarks comparing Data.Map.Strict with other dictionary -- implementations can be found at -- https://github.com/haskell-perf/dictionaries. -- --

Warning

-- -- The size of a Map must not exceed maxBound::Int. -- Violation of this condition is not detected and if the size limit is -- exceeded, its behaviour is undefined. -- -- The Map type is shared between the lazy and strict modules, -- meaning that the same Map value can be passed to functions in -- both modules. This means that the Functor, Traversable -- and Data instances are the same as for the Data.Map.Lazy -- module, so if they are used the resulting maps may contain suspended -- values (thunks). -- --

Implementation

-- -- The implementation of Map is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- module Data.Map.Strict -- | A Map from keys k to values a. -- -- The Semigroup operation for Map is union, which -- prefers values from the left operand. If m1 maps a key -- k to a value a1, and m2 maps the same key -- to a different value a2, then their union m1 <> -- m2 maps k to a1. data Map k a -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: Map k a -- | O(1). A map with a single element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: k -> a -> Map k a -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.Set.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.Set.empty == empty
--   
fromSet :: (k -> a) -> Set k -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs. See -- also fromAscList. If the list contains more than one value for -- the same key, the last value for the key is retained. -- -- If the keys of the list are ordered, linear-time implementation is -- used, with the performance equal to fromDistinctAscList. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: Ord k => [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWithKey. -- --
--   let f k a1 a2 = (show k) ++ a1 ++ a2
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "3ab"), (5, "5a5ba")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromAscList [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")]) == True
--   valid (fromAscListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctAscList [(3,"b"), (5,"a")])          == True
--   valid (fromDistinctAscList [(3,"b"), (5,"a"), (5,"b")]) == False
--   
fromDistinctAscList :: [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time. The -- precondition (input list is descending) is not checked. -- --
--   fromDescList [(5,"a"), (3,"b")]          == fromList [(3, "b"), (5, "a")]
--   fromDescList [(5,"a"), (5,"b"), (3,"a")] == fromList [(3, "b"), (5, "b")]
--   valid (fromDescList [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromDescListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctDescList [(5,"a"), (3,"b")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctDescList [(5,"a"), (3,"b")])          == True
--   valid (fromDistinctDescList [(5,"a"), (3,"b"), (3,"a")]) == False
--   
fromDistinctDescList :: [(k, a)] -> Map k a -- | O(log n). Insert a new key and value in the map. If the key is -- already present in the map, the associated value is replaced with the -- supplied value. insert is equivalent to insertWith -- const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Ord k => k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining new value and old -- value. insertWith f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert the pair (key, f -- new_value old_value). -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining key, new value and -- old value. insertWithKey f key value mp will insert -- the pair (key, value) into mp if key does not exist in the -- map. If the key does exist, the function will insert the pair -- (key,f key new_value old_value). Note that the key passed to -- f is the same key passed to insertWithKey. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Combines insert operation with old value retrieval. -- The expression (insertLookupWithKey f k x map) is a -- pair where the first element is equal to (lookup k -- map) and the second element equal to (insertWithKey f -- k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) -- | O(log n). Delete a key and its value from the map. When the key -- is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Ord k => k -> Map k a -> Map k a -- | O(log n). Update a value at a specific key with the result of -- the provided function. When the key is not a member of the map, the -- original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a -- | O(log n). Adjust a value at a specific key. When the key is not -- a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a -- | O(log n). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (updateWithKey f k -- map) updates the value x at k (if it is in the -- map). If (f k x) is Nothing, the element is deleted. -- If it is (Just y), the key k is bound to the -- new value y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). Lookup and update. See also updateWithKey. The -- function returns changed value, if it is updated. Returns the original -- key value if the map entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "5:new a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) -- | O(log n). The expression (alter f k map) alters -- the value x at k, or absence thereof. alter -- can be used to insert, delete, or update a value in a Map. In -- short : lookup k (alter f k m) = f (lookup k -- m). -- --
--   let f _ = Nothing
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
--   let f _ = Just "c"
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "c")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "c")]
--   
-- -- Note that adjust = alter . fmap. alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in a Map. In short: lookup k <$> -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> Map Int String -> IO (Map Int String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. When used with -- trivial functors like Identity and Const, it is often -- slightly slower than more specialized combinators like lookup -- and insert. However, when the functor is non-trivial and key -- comparison is not particularly cheap, it is the fastest way. -- -- Note on rewrite rules: -- -- This module includes GHC rewrite rules to optimize alterF for -- the Const and Identity functors. In general, these rules -- improve performance. The sole exception is that when using -- Identity, deleting a key that is already absent takes longer -- than it would without the rules. If you expect this to occur a very -- large fraction of the time, you might consider using a private copy of -- the Identity type. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: (Functor f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a) -- | O(log n). Lookup the value at a key in the map. -- -- The function will return the corresponding value as (Just -- value), or Nothing if the key isn't in the map. -- -- An example of using lookup: -- --
--   import Prelude hiding (lookup)
--   import Data.Map
--   
--   employeeDept = fromList([("John","Sales"), ("Bob","IT")])
--   deptCountry = fromList([("IT","USA"), ("Sales","France")])
--   countryCurrency = fromList([("USA", "Dollar"), ("France", "Euro")])
--   
--   employeeCurrency :: String -> Maybe String
--   employeeCurrency name = do
--       dept <- lookup name employeeDept
--       country <- lookup dept deptCountry
--       lookup country countryCurrency
--   
--   main = do
--       putStrLn $ "John's currency: " ++ (show (employeeCurrency "John"))
--       putStrLn $ "Pete's currency: " ++ (show (employeeCurrency "Pete"))
--   
-- -- The output of this program: -- --
--   John's currency: Just "Euro"
--   Pete's currency: Nothing
--   
lookup :: Ord k => k -> Map k a -> Maybe a -- | O(log n). Find the value at a key. Returns Nothing when -- the element can not be found. -- --
--   fromList [(5, 'a'), (3, 'b')] !? 1 == Nothing
--   
-- --
--   fromList [(5, 'a'), (3, 'b')] !? 5 == Just 'a'
--   
(!?) :: Ord k => Map k a -> k -> Maybe a infixl 9 !? -- | O(log n). Find the value at a key. Calls error when the -- element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: Ord k => Map k a -> k -> a infixl 9 ! -- | O(log n). The expression (findWithDefault def k -- map) returns the value at key k or returns default value -- def when the key is not in the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: Ord k => a -> k -> Map k a -> a -- | O(log n). Is the key a member of the map? See also -- notMember. -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Ord k => k -> Map k a -> Bool -- | O(log n). Is the key not a member of the map? See also -- member. -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Ord k => k -> Map k a -> Bool -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(1). Is the map empty? -- --
--   Data.Map.null (empty)           == True
--   Data.Map.null (singleton 1 'a') == False
--   
null :: Map k a -> Bool -- | O(1). The number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: Map k a -> Int -- | O(m*log(n/m + 1)), m <= n. The expression (union -- t1 t2) takes the left-biased union of t1 and -- t2. It prefers t1 when duplicate keys are -- encountered, i.e. (union == unionWith -- const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: Ord k => Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a -- | The union of a list of maps: (unions == foldl -- union empty). -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: (Foldable f, Ord k) => f (Map k a) -> Map k a -- | The union of a list of maps, with a combining operation: -- (unionsWith f == foldl (unionWith f) -- empty). -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: (Foldable f, Ord k) => (a -> a -> a) -> f (Map k a) -> Map k a -- | O(m*log(n/m + 1)), m <= n. Difference of two maps. Return -- elements of the first map not existing in the second map. -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: Ord k => Map k a -> Map k b -> Map k a -- | Same as difference. (\\) :: Ord k => Map k a -> Map k b -> Map k a infixl 9 \\ -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the values -- of these keys. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection of two maps. Return -- data in the first map for the keys existing in both maps. -- (intersection m1 m2 == intersectionWith const -- m1 m2). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: Ord k => Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Check whether the key sets of two -- maps are disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord k => Map k a -> Map k b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.Map.Strict exposed a version -- of compose that forced the values of the output Map. -- This version does not force these values. compose :: Ord b => Map b c -> Map a b -> Map a c -- | O(n+m). An unsafe universal combining function. -- -- WARNING: This function can produce corrupt maps and its results may -- depend on the internal structures of its inputs. Users should prefer -- merge or mergeA. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two Maps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: Ord k => (k -> a -> b -> Maybe c) -> (Map k a -> Map k c) -> (Map k b -> Map k c) -> Map k a -> Map k b -> Map k c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> Map k a -> Map k b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b -- | O(n). traverseWithKey f m == fromList -- $ traverse ((k, v) -> (v' -> v' `seq` (k,v')) -- $ f k v) (toList m) That is, it behaves much like a -- regular traverse except that the traversing function also has -- access to the key associated with a value and the values are forced -- before they are installed in the result map. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b) -- | O(n). The function mapAccum threads an accumulating -- argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n*log n). mapKeys f s is the map obtained by -- applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. The value at the greater of the two -- original keys is used as the first argument to c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). mapKeysMonotonic f s == mapKeys f -- s, but works only when f is strictly monotonic. That is, -- for any values x and y, if x < -- y then f x < f y. The precondition is -- not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   valid (mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")])) == True
--   valid (mapKeysMonotonic (\ _ -> 1)     (fromList [(5,"a"), (3,"b")])) == False
--   
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: Map k a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: Map k a -> [k] -- | O(n). An alias for toAscList. Return all key/value pairs -- in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: Map k a -> [(k, a)] -- | O(n). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.Set.fromList [3,5]
--   keysSet empty == Data.Set.empty
--   
keysSet :: Map k a -> Set k -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: Map k a -> [(k, a)] -- | O(n). Filter all values that satisfy the predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> Map k a -> Map k a -- | O(n). Filter all keys/values that satisfy the predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Restrict a Map to only -- those keys found in a Set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   m `restrictKeys` s = m `intersection` fromSet (const ()) s
--   
restrictKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(m*log(n/m + 1)), m <= n. Remove all keys in a Set -- from a Map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   m `withoutKeys` s = m `difference` fromSet (const ()) s
--   
withoutKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(log n). Take while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile (p . fst) . toList
--   takeWhileAntitone p = filterWithKey (k _ -> p k)
--   
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Drop while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile (p . fst) . toList
--   dropWhileAntitone p = filterWithKey (k -> not (p k))
--   
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Divide a map at the point where a predicate on the -- keys stops holding. The user is responsible for ensuring that for all -- keys j and k in the map, j < k ==> p j -- >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partitionWithKey (k _ -> p k) xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the map at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first key and to fail after -- the last key). spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(log n). The expression (split k map) is a -- pair (map1,map2) where the keys in map1 are smaller -- than k and the keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Ord k => k -> Map k a -> (Map k a, Map k a) -- | O(log n). The expression (splitLookup k map) -- splits a map just like split but also returns lookup -- k map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d')],fromList [(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Map k b -> [Map k b] -- | O(m*log(n/m + 1)), m <= n. This function is defined as -- (isSubmapOf = isSubmapOfBy (==)). isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. The expression -- (isSubmapOfBy f t1 t2) returns True if all keys -- in t1 are in tree t2, and when f returns -- True when applied to their respective values. For example, the -- following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<=) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1),('b',2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [('a',2)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<)  (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1)])
--   
-- -- Note that isSubmapOfBy (_ _ -> True) m1 m2 tests whether -- all the keys in m1 are also keys in m2. isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). Defined as (isProperSubmapOf = -- isProperSubmapOfBy (==)). isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). The expression (isProperSubmapOfBy f -- m1 m2) returns True when keys m1 and keys -- m2 are not equal, all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(log n). Lookup the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- --
--   isJust (lookupIndex 2 (fromList [(5,"a"), (3,"b")]))   == False
--   fromJust (lookupIndex 3 (fromList [(5,"a"), (3,"b")])) == 0
--   fromJust (lookupIndex 5 (fromList [(5,"a"), (3,"b")])) == 1
--   isJust (lookupIndex 6 (fromList [(5,"a"), (3,"b")]))   == False
--   
lookupIndex :: Ord k => k -> Map k a -> Maybe Int -- | O(log n). Return the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- Calls error when the key is not a member of the map. -- --
--   findIndex 2 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   findIndex 3 (fromList [(5,"a"), (3,"b")]) == 0
--   findIndex 5 (fromList [(5,"a"), (3,"b")]) == 1
--   findIndex 6 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   
findIndex :: Ord k => k -> Map k a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   elemAt 0 (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   elemAt 1 (fromList [(5,"a"), (3,"b")]) == (5, "a")
--   elemAt 2 (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
elemAt :: Int -> Map k a -> (k, a) -- | O(log n). Update the element at index. Calls -- error when an invalid index is used. -- --
--   updateAt (\ _ _ -> Just "x") 0    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "x"), (5, "a")]
--   updateAt (\ _ _ -> Just "x") 1    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "x")]
--   updateAt (\ _ _ -> Just "x") 2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\ _ _ -> Just "x") (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  0    (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   updateAt (\_ _  -> Nothing)  1    (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   updateAt (\_ _  -> Nothing)  2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   deleteAt 0  (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   deleteAt 1  (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   deleteAt 2 (fromList [(5,"a"), (3,"b")])     Error: index out of range
--   deleteAt (-1) (fromList [(5,"a"), (3,"b")])  Error: index out of range
--   
deleteAt :: Int -> Map k a -> Map k a -- | Take a given number of entries in key order, beginning with the -- smallest keys. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Map k a -> Map k a -- | Drop a given number of entries in key order, beginning with the -- smallest keys. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Map k a -> Map k a -- | O(log n). Split a map at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Map k a -> (Map k a, Map k a) -- | O(log n). The minimal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMin (fromList [(5,"a"), (3,"b")]) == Just (3,"b")
--   lookupMin empty = Nothing
--   
lookupMin :: Map k a -> Maybe (k, a) -- | O(log n). The maximal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMax (fromList [(5,"a"), (3,"b")]) == Just (5,"a")
--   lookupMax empty = Nothing
--   
lookupMax :: Map k a -> Maybe (k, a) -- | O(log n). The minimal key of the map. Calls error if the -- map is empty. -- --
--   findMin (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   findMin empty                            Error: empty map has no minimal element
--   
findMin :: Map k a -> (k, a) findMax :: Map k a -> (k, a) -- | O(log n). Delete the minimal key. Returns an empty map if the -- map is empty. -- --
--   deleteMin (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(5,"a"), (7,"c")]
--   deleteMin empty == empty
--   
deleteMin :: Map k a -> Map k a -- | O(log n). Delete the maximal key. Returns an empty map if the -- map is empty. -- --
--   deleteMax (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(3,"b"), (5,"a")]
--   deleteMax empty == empty
--   
deleteMax :: Map k a -> Map k a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((3,"b"), fromList[(5,"a"), (10,"c")])
--   deleteFindMin empty                                      Error: can not return the minimal element of an empty map
--   
deleteFindMin :: Map k a -> ((k, a), Map k a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((10,"c"), fromList [(3,"b"), (5,"a")])
--   deleteFindMax empty                                      Error: can not return the maximal element of an empty map
--   
deleteFindMax :: Map k a -> ((k, a), Map k a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Retrieves the value associated with minimal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   minView (fromList [(5,"a"), (3,"b")]) == Just ("b", singleton 5 "a")
--   minView empty == Nothing
--   
minView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the value associated with maximal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b")
--   maxView empty == Nothing
--   
maxView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | O(log n). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | This function has moved to showTree. showTree :: Whoops "showTree has moved to Data.Map.Internal.Debug.showTree." => Map k a -> String -- | This function has moved to showTreeWith. showTreeWith :: Whoops "showTreeWith has moved to Data.Map.Internal.Debug.showTreeWith." => (k -> a -> String) -> Bool -> Bool -> Map k a -> String -- | O(n). Test if the internal map structure is valid. -- --
--   valid (fromAscList [(3,"b"), (5,"a")]) == True
--   valid (fromAscList [(5,"a"), (3,"b")]) == False
--   
valid :: Ord k => Map k a -> Bool -- | This module defines an API for writing functions that merge two maps. -- The key functions are merge and mergeA. Each of these -- can be used with several different "merge tactics". -- -- The merge and mergeA functions are shared by the lazy -- and strict modules. Only the choice of merge tactics determines -- strictness. If you use mapMissing from this module then the -- results will be forced before they are inserted. If you use -- mapMissing from Data.Map.Merge.Lazy then they will not. -- --

preserveMissing inconsistency

-- -- For historical reasons, the preserved values are /not/ forced. -- To force them, use preserveMissing'. -- --

Efficiency note

-- -- The Category, Applicative, and Monad instances -- for WhenMissing tactics are included because they are valid. -- However, they are inefficient in many cases and should usually be -- avoided. The instances for WhenMatched tactics should not pose -- any major efficiency problems. module Data.Map.Merge.Strict -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing k x z is an abstract -- representation of a function of type k -> x -> Maybe z -- . type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched k x y z is an abstract -- representation of a function of type k -> x -> y -> -- Maybe z . type SimpleWhenMatched = WhenMatched Identity -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge preserveMissing dropMissing (zipWithMatched f)
--   
-- --
--   symmetricDifference = merge preserveMissing preserveMissing (zipWithMaybeMatched $ \ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (mapMissing f) (mapMissing g) (zipWithMatched h)
--   
merge :: Ord k => SimpleWhenMissing k a c -> SimpleWhenMissing k b c -> SimpleWhenMatched k a b c -> Map k a -> Map k b -> Map k c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched :: (k -> x -> y -> Maybe z)
--                       -> SimpleWhenMatched k x y z
--   
zipWithMaybeMatched :: Applicative f => (k -> x -> y -> Maybe z) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched :: (k -> x -> y -> z)
--                  -> SimpleWhenMatched k x y z
--   
zipWithMatched :: Applicative f => (k -> x -> y -> z) -> WhenMatched f k x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (k -> x -> Maybe y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (k -> x -> Maybe y) -> WhenMissing f k x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing k x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f k x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f k x x -- | Force the entries whose keys are missing from the other map and -- otherwise preserve them unchanged. -- --
--   preserveMissing' :: SimpleWhenMissing k x x
--   
-- --
--   preserveMissing' = Merge.Lazy.mapMaybeMissing (\_ x -> Just $! x)
--   
-- -- but preserveMissing' is quite a bit faster. preserveMissing' :: Applicative f => WhenMissing f k x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (k -> x -> y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing k x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (k -> x -> Bool) -> WhenMissing f k x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type k -> x -> f (Maybe z) -- . data WhenMissing f k x y -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f k x y z is an abstract -- representation of a function of type k -> x -> y -> f -- (Maybe z) . data WhenMatched f k x y z -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: (Applicative f, Ord k) => WhenMissing f k a c -> WhenMissing f k b c -> WhenMatched f k a b c -> Map k a -> Map k b -> f (Map k c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: Applicative f => (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (k -> x -> y -> f z) -> WhenMatched f k x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (k -> x -> f (Maybe y)) -> WhenMissing f k x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (k -> x -> f y) -> WhenMissing f k x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     k x -> (b -> guard b *> Just x) $ f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (k -> x -> f Bool) -> WhenMissing f k x x -- | Map covariantly over a WhenMissing f k x. mapWhenMissing :: Functor f => (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b -- | Map covariantly over a WhenMatched f k x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f k x y z and k -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f k x y and k -> x -> f (Maybe y). runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y) -- |

Finite Maps (lazy interface)

-- -- The Map k v type represents a finite map (sometimes -- called a dictionary) from keys of type k to values of type -- v. A Map is strict in its keys but lazy in its values. -- -- The functions in Data.Map.Strict are careful to force values -- before installing them in a Map. This is usually more efficient -- in cases where laziness is not essential. The functions in this module -- do not do so. -- -- When deciding if this is the correct data structure to use, consider: -- -- -- -- For a walkthrough of the most commonly used functions see the maps -- introduction. -- -- This module is intended to be imported qualified, to avoid name -- clashes with Prelude functions: -- --
--   import qualified Data.Map.Lazy as Map
--   
-- -- Note that the implementation is generally left-biased. -- Functions that take two maps as arguments and combine them, such as -- union and intersection, prefer the values in the first -- argument to those in the second. -- --

Detailed performance information

-- -- The amortized running time is given for each operation, with n -- referring to the number of entries in the map. -- -- Benchmarks comparing Data.Map.Lazy with other dictionary -- implementations can be found at -- https://github.com/haskell-perf/dictionaries. -- --

Warning

-- -- The size of a Map must not exceed maxBound :: -- Int. Violation of this condition is not detected and if -- the size limit is exceeded, its behaviour is undefined. -- --

Implementation

-- -- The implementation of Map is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- module Data.Map.Lazy -- | A Map from keys k to values a. -- -- The Semigroup operation for Map is union, which -- prefers values from the left operand. If m1 maps a key -- k to a value a1, and m2 maps the same key -- to a different value a2, then their union m1 <> -- m2 maps k to a1. data Map k a -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: Map k a -- | O(1). A map with a single element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: k -> a -> Map k a -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.Set.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.Set.empty == empty
--   
fromSet :: (k -> a) -> Set k -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs. See -- also fromAscList. If the list contains more than one value for -- the same key, the last value for the key is retained. -- -- If the keys of the list are ordered, linear-time implementation is -- used, with the performance equal to fromDistinctAscList. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: Ord k => [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n*log n). Build a map from a list of key/value pairs with a -- combining function. See also fromAscListWithKey. -- --
--   let f k a1 a2 = (show k) ++ a1 ++ a2
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "3ab"), (5, "5a5ba")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time. The -- precondition (input list is ascending) is not checked. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromAscList [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")]) == True
--   valid (fromAscListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromAscListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list in linear time with a -- combining function for equal keys. The precondition (input list is -- ascending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b"), (5,"b")]) == True
--   valid (fromAscListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from an ascending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctAscList [(3,"b"), (5,"a")])          == True
--   valid (fromDistinctAscList [(3,"b"), (5,"a"), (5,"b")]) == False
--   
fromDistinctAscList :: [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time. The -- precondition (input list is descending) is not checked. -- --
--   fromDescList [(5,"a"), (3,"b")]          == fromList [(3, "b"), (5, "a")]
--   fromDescList [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "b")]
--   valid (fromDescList [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescList [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescList :: Eq k => [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "ba")]
--   valid (fromDescListWith (++) [(5,"a"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWith (++) [(5,"a"), (3,"b"), (5,"b")]) == False
--   
fromDescListWith :: Eq k => (a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list in linear time with a -- combining function for equal keys. The precondition (input list is -- descending) is not checked. -- --
--   let f k a1 a2 = (show k) ++ ":" ++ a1 ++ a2
--   fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")] == fromList [(3, "b"), (5, "5:b5:ba")]
--   valid (fromDescListWithKey f [(5,"a"), (5,"b"), (5,"b"), (3,"b")]) == True
--   valid (fromDescListWithKey f [(5,"a"), (3,"b"), (5,"b"), (5,"b")]) == False
--   
fromDescListWithKey :: Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a -- | O(n). Build a map from a descending list of distinct elements -- in linear time. The precondition is not checked. -- --
--   fromDistinctDescList [(5,"a"), (3,"b")] == fromList [(3, "b"), (5, "a")]
--   valid (fromDistinctDescList [(5,"a"), (3,"b")])          == True
--   valid (fromDistinctDescList [(5,"a"), (5,"b"), (3,"b")]) == False
--   
fromDistinctDescList :: [(k, a)] -> Map k a -- | O(log n). Insert a new key and value in the map. If the key is -- already present in the map, the associated value is replaced with the -- supplied value. insert is equivalent to insertWith -- const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Ord k => k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining new value and old -- value. insertWith f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert the pair (key, f -- new_value old_value). -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Insert with a function, combining key, new value and -- old value. insertWithKey f key value mp will insert -- the pair (key, value) into mp if key does not exist in the -- map. If the key does exist, the function will insert the pair -- (key,f key new_value old_value). Note that the key passed to -- f is the same key passed to insertWithKey. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a -- | O(log n). Combines insert operation with old value retrieval. -- The expression (insertLookupWithKey f k x map) is a -- pair where the first element is equal to (lookup k -- map) and the second element equal to (insertWithKey f -- k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) -- | O(log n). Delete a key and its value from the map. When the key -- is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Ord k => k -> Map k a -> Map k a -- | O(log n). Update a value at a specific key with the result of -- the provided function. When the key is not a member of the map, the -- original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a -- | O(log n). Adjust a value at a specific key. When the key is not -- a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a -- | O(log n). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (updateWithKey f k -- map) updates the value x at k (if it is in the -- map). If (f k x) is Nothing, the element is deleted. -- If it is (Just y), the key k is bound to the -- new value y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). Lookup and update. See also updateWithKey. The -- function returns changed value, if it is updated. Returns the original -- key value if the map entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "5:new a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a) -- | O(log n). The expression (alter f k map) alters -- the value x at k, or absence thereof. alter -- can be used to insert, delete, or update a value in a Map. In -- short : lookup k (alter f k m) = f (lookup k -- m). -- --
--   let f _ = Nothing
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
--   let f _ = Just "c"
--   alter f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "c")]
--   alter f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "c")]
--   
-- -- Note that adjust = alter . fmap. alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in a Map. In short: lookup k <$> -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> Map Int String -> IO (Map Int String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. When used with -- trivial functors like Identity and Const, it is often -- slightly slower than more specialized combinators like lookup -- and insert. However, when the functor is non-trivial and key -- comparison is not particularly cheap, it is the fastest way. -- -- Note on rewrite rules: -- -- This module includes GHC rewrite rules to optimize alterF for -- the Const and Identity functors. In general, these rules -- improve performance. The sole exception is that when using -- Identity, deleting a key that is already absent takes longer -- than it would without the rules. If you expect this to occur a very -- large fraction of the time, you might consider using a private copy of -- the Identity type. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: (Functor f, Ord k) => (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a) -- | O(log n). Lookup the value at a key in the map. -- -- The function will return the corresponding value as (Just -- value), or Nothing if the key isn't in the map. -- -- An example of using lookup: -- --
--   import Prelude hiding (lookup)
--   import Data.Map
--   
--   employeeDept = fromList([("John","Sales"), ("Bob","IT")])
--   deptCountry = fromList([("IT","USA"), ("Sales","France")])
--   countryCurrency = fromList([("USA", "Dollar"), ("France", "Euro")])
--   
--   employeeCurrency :: String -> Maybe String
--   employeeCurrency name = do
--       dept <- lookup name employeeDept
--       country <- lookup dept deptCountry
--       lookup country countryCurrency
--   
--   main = do
--       putStrLn $ "John's currency: " ++ (show (employeeCurrency "John"))
--       putStrLn $ "Pete's currency: " ++ (show (employeeCurrency "Pete"))
--   
-- -- The output of this program: -- --
--   John's currency: Just "Euro"
--   Pete's currency: Nothing
--   
lookup :: Ord k => k -> Map k a -> Maybe a -- | O(log n). Find the value at a key. Returns Nothing when -- the element can not be found. -- --
--   fromList [(5, 'a'), (3, 'b')] !? 1 == Nothing
--   
-- --
--   fromList [(5, 'a'), (3, 'b')] !? 5 == Just 'a'
--   
(!?) :: Ord k => Map k a -> k -> Maybe a infixl 9 !? -- | O(log n). Find the value at a key. Calls error when the -- element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: Ord k => Map k a -> k -> a infixl 9 ! -- | O(log n). The expression (findWithDefault def k -- map) returns the value at key k or returns default value -- def when the key is not in the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: Ord k => a -> k -> Map k a -> a -- | O(log n). Is the key a member of the map? See also -- notMember. -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Ord k => k -> Map k a -> Bool -- | O(log n). Is the key not a member of the map? See also -- member. -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Ord k => k -> Map k a -> Bool -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Ord k => k -> Map k v -> Maybe (k, v) -- | O(1). Is the map empty? -- --
--   Data.Map.null (empty)           == True
--   Data.Map.null (singleton 1 'a') == False
--   
null :: Map k a -> Bool -- | O(1). The number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: Map k a -> Int -- | O(m*log(n/m + 1)), m <= n. The expression (union -- t1 t2) takes the left-biased union of t1 and -- t2. It prefers t1 when duplicate keys are -- encountered, i.e. (union == unionWith -- const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: Ord k => Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a -- | The union of a list of maps: (unions == foldl -- union empty). -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: (Foldable f, Ord k) => f (Map k a) -> Map k a -- | The union of a list of maps, with a combining operation: -- (unionsWith f == foldl (unionWith f) -- empty). -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: (Foldable f, Ord k) => (a -> a -> a) -> f (Map k a) -> Map k a -- | O(m*log(n/m + 1)), m <= n. Difference of two maps. Return -- elements of the first map not existing in the second map. -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: Ord k => Map k a -> Map k b -> Map k a -- | Same as difference. (\\) :: Ord k => Map k a -> Map k b -> Map k a infixl 9 \\ -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the values -- of these keys. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection of two maps. Return -- data in the first map for the keys existing in both maps. -- (intersection m1 m2 == intersectionWith const -- m1 m2). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: Ord k => Map k a -> Map k b -> Map k a -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Intersection with a combining -- function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c -- | O(m*log(n/m + 1)), m <= n. Check whether the key sets of two -- maps are disjoint (i.e., their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   xs `disjoint` ys = null (xs `intersection` ys)
--   
disjoint :: Ord k => Map k a -> Map k b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.Map.Strict exposed a version -- of compose that forced the values of the output Map. -- This version does not force these values. compose :: Ord b => Map b c -> Map a b -> Map a c -- | O(n+m). An unsafe general combining function. -- -- WARNING: This function can produce corrupt maps and its results may -- depend on the internal structures of its inputs. Users should prefer -- merge or mergeA. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two Maps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f, -- filterWithKey f, or mapMaybeWithKey f -- could be used for any f. mergeWithKey :: Ord k => (k -> a -> b -> Maybe c) -> (Map k a -> Map k c) -> (Map k b -> Map k c) -> Map k a -> Map k b -> Map k c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> Map k a -> Map k b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b -- | O(n). traverseWithKey f m == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (k -> a -> t b) -> Map k a -> t (Map k b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b) -- | O(n). The function mapAccum threads an accumulating -- argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) -- | O(n*log n). mapKeys f s is the map obtained by -- applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. The value at the greater of the two -- original keys is used as the first argument to c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). mapKeysMonotonic f s == mapKeys f -- s, but works only when f is strictly monotonic. That is, -- for any values x and y, if x < -- y then f x < f y. The precondition is -- not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   valid (mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")])) == True
--   valid (mapKeysMonotonic (\ _ -> 1)     (fromList [(5,"a"), (3,"b")])) == False
--   
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> Map k b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: Map k a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: Map k a -> [k] -- | O(n). An alias for toAscList. Return all key/value pairs -- in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: Map k a -> [(k, a)] -- | O(n). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.Set.fromList [3,5]
--   keysSet empty == Data.Set.empty
--   
keysSet :: Map k a -> Set k -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: Map k a -> [(k, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: Map k a -> [(k, a)] -- | O(n). Filter all values that satisfy the predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> Map k a -> Map k a -- | O(n). Filter all keys/values that satisfy the predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a -- | O(m*log(n/m + 1)), m <= n. Restrict a Map to only -- those keys found in a Set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   m `restrictKeys` s = m `intersection` fromSet (const ()) s
--   
restrictKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(m*log(n/m + 1)), m <= n. Remove all keys in a Set -- from a Map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   m `withoutKeys` s = m `difference` fromSet (const ()) s
--   
withoutKeys :: Ord k => Map k a -> Set k -> Map k a -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Partition the map according to a predicate. The first map -- contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(log n). Take while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   takeWhileAntitone p = fromDistinctAscList . takeWhile (p . fst) . toList
--   takeWhileAntitone p = filterWithKey (k _ -> p k)
--   
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Drop while a predicate on the keys holds. The user is -- responsible for ensuring that for all keys j and k -- in the map, j < k ==> p j >= p k. See note at -- spanAntitone. -- --
--   dropWhileAntitone p = fromDistinctAscList . dropWhile (p . fst) . toList
--   dropWhileAntitone p = filterWithKey (k -> not (p k))
--   
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a -- | O(log n). Divide a map at the point where a predicate on the -- keys stops holding. The user is responsible for ensuring that for all -- keys j and k in the map, j < k ==> p j -- >= p k. -- --
--   spanAntitone p xs = (takeWhileAntitone p xs, dropWhileAntitone p xs)
--   spanAntitone p xs = partitionWithKey (k _ -> p k) xs
--   
-- -- Note: if p is not actually antitone, then -- spanAntitone will split the map at some unspecified -- point where the predicate switches from holding to not holding (where -- the predicate is seen to hold before the first key and to fail after -- the last key). spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c) -- | O(log n). The expression (split k map) is a -- pair (map1,map2) where the keys in map1 are smaller -- than k and the keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Ord k => k -> Map k a -> (Map k a, Map k a) -- | O(log n). The expression (splitLookup k map) -- splits a map just like split but also returns lookup -- k map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d')],fromList [(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than three -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: Map k b -> [Map k b] -- | O(m*log(n/m + 1)), m <= n. This function is defined as -- (isSubmapOf = isSubmapOfBy (==)). isSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. The expression -- (isSubmapOfBy f t1 t2) returns True if all keys -- in t1 are in tree t2, and when f returns -- True when applied to their respective values. For example, the -- following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<=) (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1),('b',2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [('a',2)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (<)  (fromList [('a',1)]) (fromList [('a',1),('b',2)])
--   isSubmapOfBy (==) (fromList [('a',1),('b',2)]) (fromList [('a',1)])
--   
-- -- Note that isSubmapOfBy (_ _ -> True) m1 m2 tests whether -- all the keys in m1 are also keys in m2. isSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). Defined as (isProperSubmapOf = -- isProperSubmapOfBy (==)). isProperSubmapOf :: (Ord k, Eq a) => Map k a -> Map k a -> Bool -- | O(m*log(n/m + 1)), m <= n. Is this a proper submap? (ie. a -- submap but not equal). The expression (isProperSubmapOfBy f -- m1 m2) returns True when keys m1 and keys -- m2 are not equal, all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool -- | O(log n). Lookup the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- --
--   isJust (lookupIndex 2 (fromList [(5,"a"), (3,"b")]))   == False
--   fromJust (lookupIndex 3 (fromList [(5,"a"), (3,"b")])) == 0
--   fromJust (lookupIndex 5 (fromList [(5,"a"), (3,"b")])) == 1
--   isJust (lookupIndex 6 (fromList [(5,"a"), (3,"b")]))   == False
--   
lookupIndex :: Ord k => k -> Map k a -> Maybe Int -- | O(log n). Return the index of a key, which is its -- zero-based index in the sequence sorted by keys. The index is a number -- from 0 up to, but not including, the size of the map. -- Calls error when the key is not a member of the map. -- --
--   findIndex 2 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   findIndex 3 (fromList [(5,"a"), (3,"b")]) == 0
--   findIndex 5 (fromList [(5,"a"), (3,"b")]) == 1
--   findIndex 6 (fromList [(5,"a"), (3,"b")])    Error: element is not in the map
--   
findIndex :: Ord k => k -> Map k a -> Int -- | O(log n). Retrieve an element by its index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   elemAt 0 (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   elemAt 1 (fromList [(5,"a"), (3,"b")]) == (5, "a")
--   elemAt 2 (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
elemAt :: Int -> Map k a -> (k, a) -- | O(log n). Update the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   updateAt (\ _ _ -> Just "x") 0    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "x"), (5, "a")]
--   updateAt (\ _ _ -> Just "x") 1    (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "x")]
--   updateAt (\ _ _ -> Just "x") 2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\ _ _ -> Just "x") (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  0    (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   updateAt (\_ _  -> Nothing)  1    (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   updateAt (\_ _  -> Nothing)  2    (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   updateAt (\_ _  -> Nothing)  (-1) (fromList [(5,"a"), (3,"b")])    Error: index out of range
--   
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a -- | O(log n). Delete the element at index, i.e. by its -- zero-based index in the sequence sorted by keys. If the index -- is out of range (less than zero, greater or equal to size of -- the map), error is called. -- --
--   deleteAt 0  (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   deleteAt 1  (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   deleteAt 2 (fromList [(5,"a"), (3,"b")])     Error: index out of range
--   deleteAt (-1) (fromList [(5,"a"), (3,"b")])  Error: index out of range
--   
deleteAt :: Int -> Map k a -> Map k a -- | Take a given number of entries in key order, beginning with the -- smallest keys. -- --
--   take n = fromDistinctAscList . take n . toAscList
--   
take :: Int -> Map k a -> Map k a -- | Drop a given number of entries in key order, beginning with the -- smallest keys. -- --
--   drop n = fromDistinctAscList . drop n . toAscList
--   
drop :: Int -> Map k a -> Map k a -- | O(log n). Split a map at a particular index. -- --
--   splitAt !n !xs = (take n xs, drop n xs)
--   
splitAt :: Int -> Map k a -> (Map k a, Map k a) -- | O(log n). The minimal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMin (fromList [(5,"a"), (3,"b")]) == Just (3,"b")
--   lookupMin empty = Nothing
--   
lookupMin :: Map k a -> Maybe (k, a) -- | O(log n). The maximal key of the map. Returns Nothing if -- the map is empty. -- --
--   lookupMax (fromList [(5,"a"), (3,"b")]) == Just (5,"a")
--   lookupMax empty = Nothing
--   
lookupMax :: Map k a -> Maybe (k, a) -- | O(log n). The minimal key of the map. Calls error if the -- map is empty. -- --
--   findMin (fromList [(5,"a"), (3,"b")]) == (3,"b")
--   findMin empty                            Error: empty map has no minimal element
--   
findMin :: Map k a -> (k, a) findMax :: Map k a -> (k, a) -- | O(log n). Delete the minimal key. Returns an empty map if the -- map is empty. -- --
--   deleteMin (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(5,"a"), (7,"c")]
--   deleteMin empty == empty
--   
deleteMin :: Map k a -> Map k a -- | O(log n). Delete the maximal key. Returns an empty map if the -- map is empty. -- --
--   deleteMax (fromList [(5,"a"), (3,"b"), (7,"c")]) == fromList [(3,"b"), (5,"a")]
--   deleteMax empty == empty
--   
deleteMax :: Map k a -> Map k a -- | O(log n). Delete and find the minimal element. -- --
--   deleteFindMin (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((3,"b"), fromList[(5,"a"), (10,"c")])
--   deleteFindMin empty                                      Error: can not return the minimal element of an empty map
--   
deleteFindMin :: Map k a -> ((k, a), Map k a) -- | O(log n). Delete and find the maximal element. -- --
--   deleteFindMax (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((10,"c"), fromList [(3,"b"), (5,"a")])
--   deleteFindMax empty                                      Error: can not return the maximal element of an empty map
--   
deleteFindMax :: Map k a -> ((k, a), Map k a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a -- | O(log n). Retrieves the value associated with minimal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   minView (fromList [(5,"a"), (3,"b")]) == Just ("b", singleton 5 "a")
--   minView empty == Nothing
--   
minView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the value associated with maximal key of -- the map, and the map stripped of that element, or Nothing if -- passed an empty map. -- --
--   maxView (fromList [(5,"a"), (3,"b")]) == Just ("a", singleton 3 "b")
--   maxView empty == Nothing
--   
maxView :: Map k a -> Maybe (a, Map k a) -- | O(log n). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | O(log n). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a) -- | This function has moved to showTree. showTree :: Whoops "showTree has moved to Data.Map.Internal.Debug.showTree." => Map k a -> String -- | This function has moved to showTreeWith. showTreeWith :: Whoops "showTreeWith has moved to Data.Map.Internal.Debug.showTreeWith." => (k -> a -> String) -> Bool -> Bool -> Map k a -> String -- | O(n). Test if the internal map structure is valid. -- --
--   valid (fromAscList [(3,"b"), (5,"a")]) == True
--   valid (fromAscList [(5,"a"), (3,"b")]) == False
--   
valid :: Ord k => Map k a -> Bool -- | Note: You should use Data.Map.Strict instead of this -- module if: -- -- -- -- An efficient implementation of ordered maps from keys to values -- (dictionaries). -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import qualified Data.Map as Map
--   
-- -- The implementation of Map is based on size balanced -- binary trees (or trees of bounded balance) as described by: -- -- -- -- Bounds for union, intersection, and difference -- are as given by -- -- -- -- Note that the implementation is left-biased -- the elements of -- a first argument are always preferred to the second, for example in -- union or insert. -- -- Warning: The size of the map must not exceed -- maxBound::Int. Violation of this condition is not detected -- and if the size limit is exceeded, its behaviour is undefined. -- -- Operation comments contain the operation time complexity in the Big-O -- notation (http://en.wikipedia.org/wiki/Big_O_notation). module Data.Map -- | This function is being removed and is no longer usable. Use -- insertWith. insertWith' :: Whoops "Data.Map.insertWith' is gone. Use Data.Map.Strict.insertWith." => (a -> a -> a) -> k -> a -> Map k a -> Map k a -- | This function is being removed and is no longer usable. Use -- insertWithKey. insertWithKey' :: Whoops "Data.Map.insertWithKey' is gone. Use Data.Map.Strict.insertWithKey." => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a -- | This function is being removed and is no longer usable. Use -- insertLookupWithKey. insertLookupWithKey' :: Whoops "Data.Map.insertLookupWithKey' is gone. Use Data.Map.Strict.insertLookupWithKey." => (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a) -- | This function is being removed and is no longer usable. Use -- foldr. fold :: Whoops "Data.Map.fold is gone. Use foldr." => (a -> b -> b) -> b -> Map k a -> b -- | This function is being removed and is no longer usable. Use -- foldrWithKey. foldWithKey :: Whoops "Data.Map.foldWithKey is gone. Use foldrWithKey." => (k -> a -> b -> b) -> b -> Map k a -> b -- |

Finite Int Maps (strict interface)

-- -- The IntMap v type represents a finite map (sometimes -- called a dictionary) from key of type Int to values of type -- v. -- -- Each function in this module is careful to force values before -- installing them in an IntMap. This is usually more efficient -- when laziness is not necessary. When laziness is required, use -- the functions in Data.IntMap.Lazy. -- -- In particular, the functions in this module obey the following law: -- -- -- -- For a walkthrough of the most commonly used functions see the maps -- introduction. -- -- This module is intended to be imported qualified, to avoid name -- clashes with Prelude functions: -- --
--   import Data.IntMap.Strict (IntMap)
--   import qualified Data.IntMap.Strict as IntMap
--   
-- -- Note that the implementation is generally left-biased. -- Functions that take two maps as arguments and combine them, such as -- union and intersection, prefer the values in the first -- argument to those in the second. -- --

Detailed performance information

-- -- The amortized running time is given for each operation, with n -- referring to the number of entries in the map and W referring -- to the number of bits in an Int (32 or 64). -- -- Benchmarks comparing Data.IntMap.Strict with other dictionary -- implementations can be found at -- https://github.com/haskell-perf/dictionaries. -- --

Warning

-- -- The IntMap type is shared between the lazy and strict modules, -- meaning that the same IntMap value can be passed to functions -- in both modules. This means that the Functor, -- Traversable and Data instances are the same as for the -- Data.IntMap.Lazy module, so if they are used the resulting map -- may contain suspended values (thunks). -- --

Implementation

-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. Additionally, benchmarks show -- that it is also (much) faster on insertions and deletions when -- compared to a generic size-balanced map implementation (see -- Data.Map). -- -- module Data.IntMap.Strict.Internal -- | A map of integers to values a. data IntMap a type Key = Int -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: IntMap a -- | O(1). A map of one element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: Key -> a -> IntMap a -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.IntSet.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.IntSet.empty == empty
--   
fromSet :: (Key -> a) -> IntSet -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs with -- a combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Build a map from a list of key/value pairs with -- a combining function. See also fromAscListWithKey'. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   
fromAscList :: [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order and all distinct. The precondition (input -- list is strictly ascending) is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   
fromDistinctAscList :: [(Key, a)] -> IntMap a -- | O(min(n,W)). Insert a new key/value pair in the map. If the key -- is already present in the map, the associated value is replaced with -- the supplied value, i.e. insert is equivalent to -- insertWith const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWith f key value mp will insert the pair (key, -- value) into mp if key does not exist in the map. If the key -- does exist, the function will insert f new_value old_value. -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWithKey f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert f key new_value -- old_value. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
-- -- If the key exists in the map, this function is lazy in value -- but strict in the result of f. insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (insertLookupWithKey f k -- x map) is a pair where the first element is equal to -- (lookup k map) and the second element equal to -- (insertWithKey f k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). Delete a key and its value from the map. When the -- key is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f k x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Lookup and update. The function returns original -- value, if it is updated. This is different behavior than -- updateLookupWithKey. Returns the original key value if the map -- entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). The expression (alter f k map) -- alters the value x at k, or absence thereof. -- alter can be used to insert, delete, or update a value in an -- IntMap. In short : lookup k (alter f k m) = f -- (lookup k m). alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in an IntMap. In short : lookup k $ -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> IntMap String -> IO (IntMap String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a) -- | O(min(n,W)). Lookup the value at a key in the map. See also -- lookup. lookup :: Key -> IntMap a -> Maybe a -- | O(min(n,W)). Find the value at a key. Returns Nothing -- when the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] !? 1 == Nothing
--   fromList [(5,'a'), (3,'b')] !? 5 == Just 'a'
--   
(!?) :: IntMap a -> Key -> Maybe a infixl 9 !? -- | O(min(n,W)). Find the value at a key. Calls error when -- the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: IntMap a -> Key -> a -- | O(min(n,W)). The expression (findWithDefault def k -- map) returns the value at key k or returns def -- when the key is not an element of the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: a -> Key -> IntMap a -> a -- | O(min(n,W)). Is the key a member of the map? -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Key -> IntMap a -> Bool -- | O(min(n,W)). Is the key not a member of the map? -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Key -> IntMap a -> Bool -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Key -> IntMap a -> Maybe (Key, a) -- | O(1). Is the map empty? -- --
--   Data.IntMap.null (empty)           == True
--   Data.IntMap.null (singleton 1 'a') == False
--   
null :: IntMap a -> Bool -- | O(n). Number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: IntMap a -> Int -- | O(n+m). The (left-biased) union of two maps. It prefers the -- first map when duplicate keys are encountered, i.e. (union -- == unionWith const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | The union of a list of maps. -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: Foldable f => f (IntMap a) -> IntMap a -- | The union of a list of maps, with a combining operation. -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: Foldable f => (a -> a -> a) -> f (IntMap a) -> IntMap a -- | O(n+m). Difference between two maps (based on keys). -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: IntMap a -> IntMap b -> IntMap a -- | Same as difference. (\\) :: IntMap a -> IntMap b -> IntMap a infixl 9 \\ -- | O(n+m). Difference with a combining function. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). The (left-biased) intersection of two maps (based on -- keys). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: IntMap a -> IntMap b -> IntMap a -- | O(n+m). The intersection with a combining function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). The intersection with a combining function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). Check whether the key sets of two maps are disjoint -- (i.e. their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   disjoint a b == null (intersection a b)
--   
disjoint :: IntMap a -> IntMap b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.IntMap.Strict exposed a -- version of compose that forced the values of the output -- IntMap. This version does not force these values. compose :: IntMap c -> IntMap Int -> IntMap c -- | O(n+m). A high-performance universal combining function. Using -- mergeWithKey, all combining functions can be defined without -- any loss of efficiency (with exception of union, -- difference and intersection, where sharing of some nodes -- is lost with mergeWithKey). -- -- Please make sure you know what is going on when using -- mergeWithKey, otherwise you can be surprised by unexpected code -- growth or even corruption of the data structure. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define your custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two IntMaps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: (Key -> a -> b -> Maybe c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c) -> IntMap a -> IntMap b -> IntMap c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> IntMap a -> IntMap b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b -- | O(n). traverseWithKey f s == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b) -- | O(n). The function mapAccum threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n*min(n,W)). mapKeys f s is the map obtained -- by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysMonotonic f s == -- mapKeys f s, but works only when f is strictly -- monotonic. That is, for any values x and y, if -- x < y then f x < f y. The -- precondition is not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has slightly better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   
mapKeysMonotonic :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: IntMap a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: IntMap a -> [Key] -- | O(n). An alias for toAscList. Returns all key/value -- pairs in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: IntMap a -> [(Key, a)] -- | O(n*min(n,W)). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.IntSet.fromList [3,5]
--   keysSet empty == Data.IntSet.empty
--   
keysSet :: IntMap a -> IntSet -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: IntMap a -> [(Key, a)] -- | O(n). Filter all values that satisfy some predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> IntMap a -> IntMap a -- | O(n). Filter all keys/values that satisfy some predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a -- | O(n+m). The restriction of a map to the keys in a set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   
restrictKeys :: IntMap a -> IntSet -> IntMap a -- | O(n+m). Remove all the keys in a given set from a map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   
withoutKeys :: IntMap a -> IntSet -> IntMap a -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(min(n,W)). The expression (split k map) is a -- pair (map1,map2) where all keys in map1 are lower -- than k and all keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Key -> IntMap a -> (IntMap a, IntMap a) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot key was found in the original map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6::Int] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d'),(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: IntMap a -> [IntMap a] -- | O(n+m). Is this a submap? Defined as (isSubmapOf = -- isSubmapOfBy (==)). isSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). The expression (isSubmapOfBy f m1 m2) -- returns True if all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [(1,2)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- Defined as (isProperSubmapOf = isProperSubmapOfBy -- (==)). isProperSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- The expression (isProperSubmapOfBy f m1 m2) returns -- True when keys m1 and keys m2 are not equal, -- all keys in m1 are in m2, and when f -- returns True when applied to their respective values. For -- example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(min(n,W)). The minimal key of the map. Returns Nothing -- if the map is empty. lookupMin :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The maximal key of the map. Returns Nothing -- if the map is empty. lookupMax :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The minimal key of the map. Calls error if -- the map is empty. Use minViewWithKey if the map may be empty. findMin :: IntMap a -> (Key, a) -- | O(min(n,W)). The maximal key of the map. Calls error if -- the map is empty. Use maxViewWithKey if the map may be empty. findMax :: IntMap a -> (Key, a) -- | O(min(n,W)). Delete the minimal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMin :: IntMap a -> IntMap a -- | O(min(n,W)). Delete the maximal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMax :: IntMap a -> IntMap a -- | O(min(n,W)). Delete and find the minimal element. This function -- throws an error if the map is empty. Use minViewWithKey if the -- map may be empty. deleteFindMin :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Delete and find the maximal element. This function -- throws an error if the map is empty. Use maxViewWithKey if the -- map may be empty. deleteFindMax :: IntMap a -> ((Key, a), IntMap a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Retrieves the minimal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. minView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the maximal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. maxView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | O(min(n,W)). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | showTree has moved to showTree showTree :: Whoops "Data.IntMap.showTree has moved to Data.IntMap.Internal.Debug.showTree" => IntMap a -> String -- | showTreeWith has moved to showTreeWith showTreeWith :: Whoops "Data.IntMap.showTreeWith has moved to Data.IntMap.Internal.Debug.showTreeWith" => Bool -> Bool -> IntMap a -> String -- |

Finite Int Maps (strict interface)

-- -- The IntMap v type represents a finite map (sometimes -- called a dictionary) from key of type Int to values of type -- v. -- -- Each function in this module is careful to force values before -- installing them in an IntMap. This is usually more efficient -- when laziness is not necessary. When laziness is required, use -- the functions in Data.IntMap.Lazy. -- -- In particular, the functions in this module obey the following law: -- -- -- -- For a walkthrough of the most commonly used functions see the maps -- introduction. -- -- This module is intended to be imported qualified, to avoid name -- clashes with Prelude functions: -- --
--   import Data.IntMap.Strict (IntMap)
--   import qualified Data.IntMap.Strict as IntMap
--   
-- -- Note that the implementation is generally left-biased. -- Functions that take two maps as arguments and combine them, such as -- union and intersection, prefer the values in the first -- argument to those in the second. -- --

Detailed performance information

-- -- The amortized running time is given for each operation, with n -- referring to the number of entries in the map and W referring -- to the number of bits in an Int (32 or 64). -- -- Benchmarks comparing Data.IntMap.Strict with other dictionary -- implementations can be found at -- https://github.com/haskell-perf/dictionaries. -- --

Warning

-- -- The IntMap type is shared between the lazy and strict modules, -- meaning that the same IntMap value can be passed to functions -- in both modules. This means that the Functor, -- Traversable and Data instances are the same as for the -- Data.IntMap.Lazy module, so if they are used the resulting map -- may contain suspended values (thunks). -- --

Implementation

-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. Additionally, benchmarks show -- that it is also (much) faster on insertions and deletions when -- compared to a generic size-balanced map implementation (see -- Data.Map). -- -- module Data.IntMap.Strict -- | A map of integers to values a. data IntMap a type Key = Int -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: IntMap a -- | O(1). A map of one element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: Key -> a -> IntMap a -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.IntSet.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.IntSet.empty == empty
--   
fromSet :: (Key -> a) -> IntSet -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs with -- a combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Build a map from a list of key/value pairs with -- a combining function. See also fromAscListWithKey'. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"a")] == fromList [(3, "ab"), (5, "aba")]
--   fromListWith (++) [] == empty
--   
fromListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   
fromAscList :: [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order and all distinct. The precondition (input -- list is strictly ascending) is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   
fromDistinctAscList :: [(Key, a)] -> IntMap a -- | O(min(n,W)). Insert a new key/value pair in the map. If the key -- is already present in the map, the associated value is replaced with -- the supplied value, i.e. insert is equivalent to -- insertWith const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWith f key value mp will insert the pair (key, -- value) into mp if key does not exist in the map. If the key -- does exist, the function will insert f new_value old_value. -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWithKey f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert f key new_value -- old_value. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
-- -- If the key exists in the map, this function is lazy in value -- but strict in the result of f. insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (insertLookupWithKey f k -- x map) is a pair where the first element is equal to -- (lookup k map) and the second element equal to -- (insertWithKey f k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). Delete a key and its value from the map. When the -- key is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f k x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Lookup and update. The function returns original -- value, if it is updated. This is different behavior than -- updateLookupWithKey. Returns the original key value if the map -- entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). The expression (alter f k map) -- alters the value x at k, or absence thereof. -- alter can be used to insert, delete, or update a value in an -- IntMap. In short : lookup k (alter f k m) = f -- (lookup k m). alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in an IntMap. In short : lookup k $ -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> IntMap String -> IO (IntMap String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a) -- | O(min(n,W)). Lookup the value at a key in the map. See also -- lookup. lookup :: Key -> IntMap a -> Maybe a -- | O(min(n,W)). Find the value at a key. Returns Nothing -- when the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] !? 1 == Nothing
--   fromList [(5,'a'), (3,'b')] !? 5 == Just 'a'
--   
(!?) :: IntMap a -> Key -> Maybe a infixl 9 !? -- | O(min(n,W)). Find the value at a key. Calls error when -- the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: IntMap a -> Key -> a -- | O(min(n,W)). The expression (findWithDefault def k -- map) returns the value at key k or returns def -- when the key is not an element of the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: a -> Key -> IntMap a -> a -- | O(min(n,W)). Is the key a member of the map? -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Key -> IntMap a -> Bool -- | O(min(n,W)). Is the key not a member of the map? -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Key -> IntMap a -> Bool -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Key -> IntMap a -> Maybe (Key, a) -- | O(1). Is the map empty? -- --
--   Data.IntMap.null (empty)           == True
--   Data.IntMap.null (singleton 1 'a') == False
--   
null :: IntMap a -> Bool -- | O(n). Number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: IntMap a -> Int -- | O(n+m). The (left-biased) union of two maps. It prefers the -- first map when duplicate keys are encountered, i.e. (union -- == unionWith const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | The union of a list of maps. -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: Foldable f => f (IntMap a) -> IntMap a -- | The union of a list of maps, with a combining operation. -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: Foldable f => (a -> a -> a) -> f (IntMap a) -> IntMap a -- | O(n+m). Difference between two maps (based on keys). -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: IntMap a -> IntMap b -> IntMap a -- | Same as difference. (\\) :: IntMap a -> IntMap b -> IntMap a infixl 9 \\ -- | O(n+m). Difference with a combining function. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). The (left-biased) intersection of two maps (based on -- keys). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: IntMap a -> IntMap b -> IntMap a -- | O(n+m). The intersection with a combining function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). The intersection with a combining function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). Check whether the key sets of two maps are disjoint -- (i.e. their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   disjoint a b == null (intersection a b)
--   
disjoint :: IntMap a -> IntMap b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.IntMap.Strict exposed a -- version of compose that forced the values of the output -- IntMap. This version does not force these values. compose :: IntMap c -> IntMap Int -> IntMap c -- | O(n+m). A high-performance universal combining function. Using -- mergeWithKey, all combining functions can be defined without -- any loss of efficiency (with exception of union, -- difference and intersection, where sharing of some nodes -- is lost with mergeWithKey). -- -- Please make sure you know what is going on when using -- mergeWithKey, otherwise you can be surprised by unexpected code -- growth or even corruption of the data structure. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define your custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two IntMaps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: (Key -> a -> b -> Maybe c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c) -> IntMap a -> IntMap b -> IntMap c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> IntMap a -> IntMap b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b -- | O(n). traverseWithKey f s == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b) -- | O(n). The function mapAccum threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n*min(n,W)). mapKeys f s is the map obtained -- by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n*log n). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysMonotonic f s == -- mapKeys f s, but works only when f is strictly -- monotonic. That is, for any values x and y, if -- x < y then f x < f y. The -- precondition is not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has slightly better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   
mapKeysMonotonic :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: IntMap a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: IntMap a -> [Key] -- | O(n). An alias for toAscList. Returns all key/value -- pairs in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: IntMap a -> [(Key, a)] -- | O(n*min(n,W)). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.IntSet.fromList [3,5]
--   keysSet empty == Data.IntSet.empty
--   
keysSet :: IntMap a -> IntSet -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: IntMap a -> [(Key, a)] -- | O(n). Filter all values that satisfy some predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> IntMap a -> IntMap a -- | O(n). Filter all keys/values that satisfy some predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a -- | O(n+m). The restriction of a map to the keys in a set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   
restrictKeys :: IntMap a -> IntSet -> IntMap a -- | O(n+m). Remove all the keys in a given set from a map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   
withoutKeys :: IntMap a -> IntSet -> IntMap a -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(min(n,W)). The expression (split k map) is a -- pair (map1,map2) where all keys in map1 are lower -- than k and all keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Key -> IntMap a -> (IntMap a, IntMap a) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot key was found in the original map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6::Int] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d'),(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: IntMap a -> [IntMap a] -- | O(n+m). Is this a submap? Defined as (isSubmapOf = -- isSubmapOfBy (==)). isSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). The expression (isSubmapOfBy f m1 m2) -- returns True if all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [(1,2)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- Defined as (isProperSubmapOf = isProperSubmapOfBy -- (==)). isProperSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- The expression (isProperSubmapOfBy f m1 m2) returns -- True when keys m1 and keys m2 are not equal, -- all keys in m1 are in m2, and when f -- returns True when applied to their respective values. For -- example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(min(n,W)). The minimal key of the map. Returns Nothing -- if the map is empty. lookupMin :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The maximal key of the map. Returns Nothing -- if the map is empty. lookupMax :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The minimal key of the map. Calls error if -- the map is empty. Use minViewWithKey if the map may be empty. findMin :: IntMap a -> (Key, a) -- | O(min(n,W)). The maximal key of the map. Calls error if -- the map is empty. Use maxViewWithKey if the map may be empty. findMax :: IntMap a -> (Key, a) -- | O(min(n,W)). Delete the minimal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMin :: IntMap a -> IntMap a -- | O(min(n,W)). Delete the maximal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMax :: IntMap a -> IntMap a -- | O(min(n,W)). Delete and find the minimal element. This function -- throws an error if the map is empty. Use minViewWithKey if the -- map may be empty. deleteFindMin :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Delete and find the maximal element. This function -- throws an error if the map is empty. Use maxViewWithKey if the -- map may be empty. deleteFindMax :: IntMap a -> ((Key, a), IntMap a) -- | O(log n). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(log n). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Retrieves the minimal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. minView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the maximal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. maxView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | O(min(n,W)). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | showTree has moved to showTree showTree :: Whoops "Data.IntMap.showTree has moved to Data.IntMap.Internal.Debug.showTree" => IntMap a -> String -- | showTreeWith has moved to showTreeWith showTreeWith :: Whoops "Data.IntMap.showTreeWith has moved to Data.IntMap.Internal.Debug.showTreeWith" => Bool -> Bool -> IntMap a -> String -- | This module defines an API for writing functions that merge two maps. -- The key functions are merge and mergeA. Each of these -- can be used with several different "merge tactics". -- -- The merge and mergeA functions are shared by the lazy -- and strict modules. Only the choice of merge tactics determines -- strictness. If you use mapMissing from this module then the -- results will be forced before they are inserted. If you use -- mapMissing from Data.Map.Merge.Lazy then they will not. -- --

Efficiency note

-- -- The Category, Applicative, and Monad instances -- for WhenMissing tactics are included because they are valid. -- However, they are inefficient in many cases and should usually be -- avoided. The instances for WhenMatched tactics should not pose -- any major efficiency problems. module Data.IntMap.Merge.Strict -- | A tactic for dealing with keys present in one map but not the other in -- merge. -- -- A tactic of type SimpleWhenMissing x z is an abstract -- representation of a function of type Key -> x -> Maybe -- z. type SimpleWhenMissing = WhenMissing Identity -- | A tactic for dealing with keys present in both maps in merge. -- -- A tactic of type SimpleWhenMatched x y z is an abstract -- representation of a function of type Key -> x -> y -> -- Maybe z. type SimpleWhenMatched = WhenMatched Identity -- | Merge two maps. -- -- merge takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- mapMaybeMissing and zipWithMaybeMatched. -- -- Consider -- --
--   merge (mapMaybeMissing g1)
--                (mapMaybeMissing g2)
--                (zipWithMaybeMatched f)
--                m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3, 'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- merge will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   maybes = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- This produces a Maybe for each key: -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- mapMaybeMissing for special cases. Most importantly, -- -- -- -- When merge is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should typically use -- merge to define your custom combining functions. -- -- Examples: -- --
--   unionWithKey f = merge preserveMissing preserveMissing (zipWithMatched f)
--   
-- --
--   intersectionWithKey f = merge dropMissing dropMissing (zipWithMatched f)
--   
-- --
--   differenceWith f = merge diffPreserve diffDrop f
--   
-- --
--   symmetricDifference = merge diffPreserve diffPreserve (\ _ _ _ -> Nothing)
--   
-- --
--   mapEachPiece f g h = merge (diffMapWithKey f) (diffMapWithKey g)
--   
merge :: SimpleWhenMissing a c -> SimpleWhenMissing b c -> SimpleWhenMatched a b c -> IntMap a -> IntMap b -> IntMap c -- | When a key is found in both maps, apply a function to the key and -- values and maybe use the result in the merged map. -- --
--   zipWithMaybeMatched :: (k -> x -> y -> Maybe z)
--                       -> SimpleWhenMatched k x y z
--   
zipWithMaybeMatched :: Applicative f => (Key -> x -> y -> Maybe z) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values and use the result in the merged map. -- --
--   zipWithMatched :: (k -> x -> y -> z)
--                  -> SimpleWhenMatched k x y z
--   
zipWithMatched :: Applicative f => (Key -> x -> y -> z) -> WhenMatched f x y z -- | Map over the entries whose keys are missing from the other map, -- optionally removing some. This is the most powerful -- SimpleWhenMissing tactic, but others are usually more -- efficient. -- --
--   mapMaybeMissing :: (k -> x -> Maybe y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMaybeMissing f = traverseMaybeMissing (\k x -> pure (f k x))
--   
-- -- but mapMaybeMissing uses fewer unnecessary Applicative -- operations. mapMaybeMissing :: Applicative f => (Key -> x -> Maybe y) -> WhenMissing f x y -- | Drop all the entries whose keys are missing from the other map. -- --
--   dropMissing :: SimpleWhenMissing x y
--   
-- --
--   dropMissing = mapMaybeMissing (\_ _ -> Nothing)
--   
-- -- but dropMissing is much faster. dropMissing :: Applicative f => WhenMissing f x y -- | Preserve, unchanged, the entries whose keys are missing from the other -- map. -- --
--   preserveMissing :: SimpleWhenMissing x x
--   
-- --
--   preserveMissing = Merge.Lazy.mapMaybeMissing (\_ x -> Just x)
--   
-- -- but preserveMissing is much faster. preserveMissing :: Applicative f => WhenMissing f x x -- | Map over the entries whose keys are missing from the other map. -- --
--   mapMissing :: (k -> x -> y) -> SimpleWhenMissing k x y
--   
-- --
--   mapMissing f = mapMaybeMissing (\k x -> Just $ f k x)
--   
-- -- but mapMissing is somewhat faster. mapMissing :: Applicative f => (Key -> x -> y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map. -- --
--   filterMissing :: (k -> x -> Bool) -> SimpleWhenMissing x x
--   
-- --
--   filterMissing f = Merge.Lazy.mapMaybeMissing $ \k x -> guard (f k x) *> Just x
--   
-- -- but this should be a little faster. filterMissing :: Applicative f => (Key -> x -> Bool) -> WhenMissing f x x -- | A tactic for dealing with keys present in one map but not the other in -- merge or mergeA. -- -- A tactic of type WhenMissing f k x z is an abstract -- representation of a function of type Key -> x -> f (Maybe -- z). data WhenMissing f x y -- | A tactic for dealing with keys present in both maps in merge or -- mergeA. -- -- A tactic of type WhenMatched f x y z is an abstract -- representation of a function of type Key -> x -> y -> f -- (Maybe z). data WhenMatched f x y z -- | An applicative version of merge. -- -- mergeA takes two WhenMissing tactics, a -- WhenMatched tactic and two maps. It uses the tactics to merge -- the maps. Its behavior is best understood via its fundamental tactics, -- traverseMaybeMissing and zipWithMaybeAMatched. -- -- Consider -- --
--   mergeA (traverseMaybeMissing g1)
--                 (traverseMaybeMissing g2)
--                 (zipWithMaybeAMatched f)
--                 m1 m2
--   
-- -- Take, for example, -- --
--   m1 = [(0, 'a'), (1, 'b'), (3,'c'), (4, 'd')]
--   m2 = [(1, "one"), (2, "two"), (4, "three")]
--   
-- -- mergeA will first "align" these maps by key: -- --
--   m1 = [(0, 'a'), (1, 'b'),               (3, 'c'), (4, 'd')]
--   m2 =           [(1, "one"), (2, "two"),           (4, "three")]
--   
-- -- It will then pass the individual entries and pairs of entries to -- g1, g2, or f as appropriate: -- --
--   actions = [g1 0 'a', f 1 'b' "one", g2 2 "two", g1 3 'c', f 4 'd' "three"]
--   
-- -- Next, it will perform the actions in the actions list in -- order from left to right. -- --
--   keys =     0        1          2           3        4
--   results = [Nothing, Just True, Just False, Nothing, Just True]
--   
-- -- Finally, the Just results are collected into a map: -- --
--   return value = [(1, True), (2, False), (4, True)]
--   
-- -- The other tactics below are optimizations or simplifications of -- traverseMaybeMissing for special cases. Most importantly, -- -- -- -- When mergeA is given three arguments, it is inlined at the call -- site. To prevent excessive inlining, you should generally only use -- mergeA to define custom combining functions. mergeA :: Applicative f => WhenMissing f a c -> WhenMissing f b c -> WhenMatched f a b c -> IntMap a -> IntMap b -> f (IntMap c) -- | When a key is found in both maps, apply a function to the key and -- values, perform the resulting action, and maybe use the result in the -- merged map. -- -- This is the fundamental WhenMatched tactic. zipWithMaybeAMatched :: Applicative f => (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z -- | When a key is found in both maps, apply a function to the key and -- values to produce an action and use its result in the merged map. zipWithAMatched :: Applicative f => (Key -> x -> y -> f z) -> WhenMatched f x y z -- | Traverse over the entries whose keys are missing from the other map, -- optionally producing values to put in the result. This is the most -- powerful WhenMissing tactic, but others are usually more -- efficient. traverseMaybeMissing :: Applicative f => (Key -> x -> f (Maybe y)) -> WhenMissing f x y -- | Traverse over the entries whose keys are missing from the other map. traverseMissing :: Applicative f => (Key -> x -> f y) -> WhenMissing f x y -- | Filter the entries whose keys are missing from the other map using -- some Applicative action. -- --
--   filterAMissing f = Merge.Lazy.traverseMaybeMissing $
--     \k x -> (\b -> guard b *> Just x) <$> f k x
--   
-- -- but this should be a little faster. filterAMissing :: Applicative f => (Key -> x -> f Bool) -> WhenMissing f x x -- | Map covariantly over a WhenMissing f k x. mapWhenMissing :: Functor f => (a -> b) -> WhenMissing f x a -> WhenMissing f x b -- | Map covariantly over a WhenMatched f k x y. mapWhenMatched :: Functor f => (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b -- | Along with zipWithMaybeAMatched, witnesses the isomorphism between -- WhenMatched f x y z and Key -> x -> y -> f -- (Maybe z). runWhenMatched :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z) -- | Along with traverseMaybeMissing, witnesses the isomorphism between -- WhenMissing f x y and Key -> x -> f (Maybe y). runWhenMissing :: WhenMissing f x y -> Key -> x -> f (Maybe y) -- |

Finite Int Maps (lazy interface)

-- -- The IntMap v type represents a finite map (sometimes -- called a dictionary) from keys of type Int to values of type -- v. -- -- The functions in Data.IntMap.Strict are careful to force values -- before installing them in an IntMap. This is usually more -- efficient in cases where laziness is not essential. The functions in -- this module do not do so. -- -- For a walkthrough of the most commonly used functions see the maps -- introduction. -- -- This module is intended to be imported qualified, to avoid name -- clashes with Prelude functions: -- --
--   import Data.IntMap.Lazy (IntMap)
--   import qualified Data.IntMap.Lazy as IntMap
--   
-- -- Note that the implementation is generally left-biased. -- Functions that take two maps as arguments and combine them, such as -- union and intersection, prefer the values in the first -- argument to those in the second. -- --

Detailed performance information

-- -- The amortized running time is given for each operation, with n -- referring to the number of entries in the map and W referring -- to the number of bits in an Int (32 or 64). -- -- Benchmarks comparing Data.IntMap.Lazy with other dictionary -- implementations can be found at -- https://github.com/haskell-perf/dictionaries. -- --

Implementation

-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. Additionally, benchmarks show -- that it is also (much) faster on insertions and deletions when -- compared to a generic size-balanced map implementation (see -- Data.Map). -- -- module Data.IntMap.Lazy -- | A map of integers to values a. data IntMap a type Key = Int -- | O(1). The empty map. -- --
--   empty      == fromList []
--   size empty == 0
--   
empty :: IntMap a -- | O(1). A map of one element. -- --
--   singleton 1 'a'        == fromList [(1, 'a')]
--   size (singleton 1 'a') == 1
--   
singleton :: Key -> a -> IntMap a -- | O(n). Build a map from a set of keys and a function which for -- each key computes its value. -- --
--   fromSet (\k -> replicate k 'a') (Data.IntSet.fromList [3, 5]) == fromList [(5,"aaaaa"), (3,"aaa")]
--   fromSet undefined Data.IntSet.empty == empty
--   
fromSet :: (Key -> a) -> IntSet -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs. -- --
--   fromList [] == empty
--   fromList [(5,"a"), (3,"b"), (5, "c")] == fromList [(5,"c"), (3,"b")]
--   fromList [(5,"c"), (3,"b"), (5, "a")] == fromList [(5,"a"), (3,"b")]
--   
fromList :: [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Create a map from a list of key/value pairs with -- a combining function. See also fromAscListWith. -- --
--   fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")] == fromList [(3, "ab"), (5, "cba")]
--   fromListWith (++) [] == empty
--   
fromListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n*min(n,W)). Build a map from a list of key/value pairs with -- a combining function. See also fromAscListWithKey'. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")] == fromList [(3, "3:a|b"), (5, "5:c|5:b|a")]
--   fromListWithKey f [] == empty
--   
fromListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order. -- --
--   fromAscList [(3,"b"), (5,"a")]          == fromList [(3, "b"), (5, "a")]
--   fromAscList [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "b")]
--   
fromAscList :: [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   fromAscListWith (++) [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "ba")]
--   
fromAscListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order, with a combining function on equal keys. -- The precondition (input list is ascending) is not checked. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   fromAscListWithKey f [(3,"b"), (5,"a"), (5,"b")] == fromList [(3, "b"), (5, "5:b|a")]
--   
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a -- | O(n). Build a map from a list of key/value pairs where the keys -- are in ascending order and all distinct. The precondition (input -- list is strictly ascending) is not checked. -- --
--   fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
--   
fromDistinctAscList :: [(Key, a)] -> IntMap a -- | O(min(n,W)). Insert a new key/value pair in the map. If the key -- is already present in the map, the associated value is replaced with -- the supplied value, i.e. insert is equivalent to -- insertWith const. -- --
--   insert 5 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'x')]
--   insert 7 'x' (fromList [(5,'a'), (3,'b')]) == fromList [(3, 'b'), (5, 'a'), (7, 'x')]
--   insert 5 'x' empty                         == singleton 5 'x'
--   
insert :: Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWith f key value mp will insert the pair (key, -- value) into mp if key does not exist in the map. If the key -- does exist, the function will insert f new_value old_value. -- --
--   insertWith (++) 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "xxxa")]
--   insertWith (++) 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWith (++) 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). Insert with a combining function. -- insertWithKey f key value mp will insert the pair -- (key, value) into mp if key does not exist in the map. If the -- key does exist, the function will insert f key new_value -- old_value. -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:xxx|a")]
--   insertWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a"), (7, "xxx")]
--   insertWithKey f 5 "xxx" empty                         == singleton 5 "xxx"
--   
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (insertLookupWithKey f k -- x map) is a pair where the first element is equal to -- (lookup k map) and the second element equal to -- (insertWithKey f k x map). -- --
--   let f key new_value old_value = (show key) ++ ":" ++ new_value ++ "|" ++ old_value
--   insertLookupWithKey f 5 "xxx" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:xxx|a")])
--   insertLookupWithKey f 7 "xxx" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "xxx")])
--   insertLookupWithKey f 5 "xxx" empty                         == (Nothing,  singleton 5 "xxx")
--   
-- -- This is how to define insertLookup using -- insertLookupWithKey: -- --
--   let insertLookup kx x t = insertLookupWithKey (\_ a _ -> a) kx x t
--   insertLookup 5 "x" (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "x")])
--   insertLookup 7 "x" (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a"), (7, "x")])
--   
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). Delete a key and its value from the map. When the -- key is not a member of the map, the original map is returned. -- --
--   delete 5 (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   delete 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   delete 5 empty                         == empty
--   
delete :: Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   adjust ("new " ++) 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   adjust ("new " ++) 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjust ("new " ++) 7 empty                         == empty
--   
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Adjust a value at a specific key. When the key is -- not a member of the map, the original map is returned. -- --
--   let f key x = (show key) ++ ":new " ++ x
--   adjustWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   adjustWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   adjustWithKey f 7 empty                         == empty
--   
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   update f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "new a")]
--   update f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   update f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). The expression (update f k map) -- updates the value x at k (if it is in the map). If -- (f k x) is Nothing, the element is deleted. If it is -- (Just y), the key k is bound to the new value -- y. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateWithKey f 5 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "5:new a")]
--   updateWithKey f 7 (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "a")]
--   updateWithKey f 3 (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(min(n,W)). Lookup and update. The function returns original -- value, if it is updated. This is different behavior than -- updateLookupWithKey. Returns the original key value if the map -- entry is deleted. -- --
--   let f k x = if x == "a" then Just ((show k) ++ ":new a") else Nothing
--   updateLookupWithKey f 5 (fromList [(5,"a"), (3,"b")]) == (Just "a", fromList [(3, "b"), (5, "5:new a")])
--   updateLookupWithKey f 7 (fromList [(5,"a"), (3,"b")]) == (Nothing,  fromList [(3, "b"), (5, "a")])
--   updateLookupWithKey f 3 (fromList [(5,"a"), (3,"b")]) == (Just "b", singleton 5 "a")
--   
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a) -- | O(min(n,W)). The expression (alter f k map) -- alters the value x at k, or absence thereof. -- alter can be used to insert, delete, or update a value in an -- IntMap. In short : lookup k (alter f k m) = f -- (lookup k m). alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a -- | O(log n). The expression (alterF f k map) -- alters the value x at k, or absence thereof. -- alterF can be used to inspect, insert, delete, or update a -- value in an IntMap. In short : lookup k $ -- alterF f k m = f (lookup k m). -- -- Example: -- --
--   interactiveAlter :: Int -> IntMap String -> IO (IntMap String)
--   interactiveAlter k m = alterF f k m where
--     f Nothing = do
--        putStrLn $ show k ++
--            " was not found in the map. Would you like to add it?"
--        getUserResponse1 :: IO (Maybe String)
--     f (Just old) = do
--        putStrLn $ "The key is currently bound to " ++ show old ++
--            ". Would you like to change or delete it?"
--        getUserResponse2 :: IO (Maybe String)
--   
-- -- alterF is the most general operation for working with an -- individual key that may or may not be in a given map. -- -- Note: alterF is a flipped version of the at combinator -- from Control.Lens.At. alterF :: Functor f => (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a) -- | O(min(n,W)). Lookup the value at a key in the map. See also -- lookup. lookup :: Key -> IntMap a -> Maybe a -- | O(min(n,W)). Find the value at a key. Returns Nothing -- when the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] !? 1 == Nothing
--   fromList [(5,'a'), (3,'b')] !? 5 == Just 'a'
--   
(!?) :: IntMap a -> Key -> Maybe a infixl 9 !? -- | O(min(n,W)). Find the value at a key. Calls error when -- the element can not be found. -- --
--   fromList [(5,'a'), (3,'b')] ! 1    Error: element not in the map
--   fromList [(5,'a'), (3,'b')] ! 5 == 'a'
--   
(!) :: IntMap a -> Key -> a -- | O(min(n,W)). The expression (findWithDefault def k -- map) returns the value at key k or returns def -- when the key is not an element of the map. -- --
--   findWithDefault 'x' 1 (fromList [(5,'a'), (3,'b')]) == 'x'
--   findWithDefault 'x' 5 (fromList [(5,'a'), (3,'b')]) == 'a'
--   
findWithDefault :: a -> Key -> IntMap a -> a -- | O(min(n,W)). Is the key a member of the map? -- --
--   member 5 (fromList [(5,'a'), (3,'b')]) == True
--   member 1 (fromList [(5,'a'), (3,'b')]) == False
--   
member :: Key -> IntMap a -> Bool -- | O(min(n,W)). Is the key not a member of the map? -- --
--   notMember 5 (fromList [(5,'a'), (3,'b')]) == False
--   notMember 1 (fromList [(5,'a'), (3,'b')]) == True
--   
notMember :: Key -> IntMap a -> Bool -- | O(log n). Find largest key smaller than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupLT 3 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLT 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   
lookupLT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater than the given one and -- return the corresponding (key, value) pair. -- --
--   lookupGT 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGT 5 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGT :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find largest key smaller or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupLE 2 (fromList [(3,'a'), (5,'b')]) == Nothing
--   lookupLE 4 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupLE 5 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   
lookupLE :: Key -> IntMap a -> Maybe (Key, a) -- | O(log n). Find smallest key greater or equal to the given one -- and return the corresponding (key, value) pair. -- --
--   lookupGE 3 (fromList [(3,'a'), (5,'b')]) == Just (3, 'a')
--   lookupGE 4 (fromList [(3,'a'), (5,'b')]) == Just (5, 'b')
--   lookupGE 6 (fromList [(3,'a'), (5,'b')]) == Nothing
--   
lookupGE :: Key -> IntMap a -> Maybe (Key, a) -- | O(1). Is the map empty? -- --
--   Data.IntMap.null (empty)           == True
--   Data.IntMap.null (singleton 1 'a') == False
--   
null :: IntMap a -> Bool -- | O(n). Number of elements in the map. -- --
--   size empty                                   == 0
--   size (singleton 1 'a')                       == 1
--   size (fromList([(1,'a'), (2,'c'), (3,'b')])) == 3
--   
size :: IntMap a -> Int -- | O(n+m). The (left-biased) union of two maps. It prefers the -- first map when duplicate keys are encountered, i.e. (union -- == unionWith const). -- --
--   union (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "a"), (7, "C")]
--   
union :: IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   unionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "aA"), (7, "C")]
--   
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | O(n+m). The union with a combining function. -- --
--   let f key left_value right_value = (show key) ++ ":" ++ left_value ++ "|" ++ right_value
--   unionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == fromList [(3, "b"), (5, "5:a|A"), (7, "C")]
--   
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a -- | The union of a list of maps. -- --
--   unions [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "b"), (5, "a"), (7, "C")]
--   unions [(fromList [(5, "A3"), (3, "B3")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "a"), (3, "b")])]
--       == fromList [(3, "B3"), (5, "A3"), (7, "C")]
--   
unions :: Foldable f => f (IntMap a) -> IntMap a -- | The union of a list of maps, with a combining operation. -- --
--   unionsWith (++) [(fromList [(5, "a"), (3, "b")]), (fromList [(5, "A"), (7, "C")]), (fromList [(5, "A3"), (3, "B3")])]
--       == fromList [(3, "bB3"), (5, "aAA3"), (7, "C")]
--   
unionsWith :: Foldable f => (a -> a -> a) -> f (IntMap a) -> IntMap a -- | O(n+m). Difference between two maps (based on keys). -- --
--   difference (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 3 "b"
--   
difference :: IntMap a -> IntMap b -> IntMap a -- | Same as difference. (\\) :: IntMap a -> IntMap b -> IntMap a infixl 9 \\ -- | O(n+m). Difference with a combining function. -- --
--   let f al ar = if al == "b" then Just (al ++ ":" ++ ar) else Nothing
--   differenceWith f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (7, "C")])
--       == singleton 3 "b:B"
--   
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). Difference with a combining function. When two equal -- keys are encountered, the combining function is applied to the key and -- both values. If it returns Nothing, the element is discarded -- (proper set difference). If it returns (Just y), the -- element is updated with a new value y. -- --
--   let f k al ar = if al == "b" then Just ((show k) ++ ":" ++ al ++ "|" ++ ar) else Nothing
--   differenceWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (3, "B"), (10, "C")])
--       == singleton 3 "3:b|B"
--   
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a -- | O(n+m). The (left-biased) intersection of two maps (based on -- keys). -- --
--   intersection (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "a"
--   
intersection :: IntMap a -> IntMap b -> IntMap a -- | O(n+m). The intersection with a combining function. -- --
--   intersectionWith (++) (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "aA"
--   
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). The intersection with a combining function. -- --
--   let f k al ar = (show k) ++ ":" ++ al ++ "|" ++ ar
--   intersectionWithKey f (fromList [(5, "a"), (3, "b")]) (fromList [(5, "A"), (7, "C")]) == singleton 5 "5:a|A"
--   
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c -- | O(n+m). Check whether the key sets of two maps are disjoint -- (i.e. their intersection is empty). -- --
--   disjoint (fromList [(2,'a')]) (fromList [(1,()), (3,())])   == True
--   disjoint (fromList [(2,'a')]) (fromList [(1,'a'), (2,'b')]) == False
--   disjoint (fromList [])        (fromList [])                 == True
--   
-- --
--   disjoint a b == null (intersection a b)
--   
disjoint :: IntMap a -> IntMap b -> Bool -- | Relate the keys of one map to the values of the other, by using the -- values of the former as keys for lookups in the latter. -- -- Complexity: <math>, where <math> is the size of the first -- argument -- --
--   compose (fromList [('a', "A"), ('b', "B")]) (fromList [(1,'a'),(2,'b'),(3,'z')]) = fromList [(1,"A"),(2,"B")]
--   
-- --
--   (compose bc ab !?) = (bc !?) <=< (ab !?)
--   
-- -- Note: Prior to v0.6.4, Data.IntMap.Strict exposed a -- version of compose that forced the values of the output -- IntMap. This version does not force these values. compose :: IntMap c -> IntMap Int -> IntMap c -- | O(n+m). A high-performance universal combining function. Using -- mergeWithKey, all combining functions can be defined without -- any loss of efficiency (with exception of union, -- difference and intersection, where sharing of some nodes -- is lost with mergeWithKey). -- -- Please make sure you know what is going on when using -- mergeWithKey, otherwise you can be surprised by unexpected code -- growth or even corruption of the data structure. -- -- When mergeWithKey is given three arguments, it is inlined to -- the call site. You should therefore use mergeWithKey only to -- define your custom combining functions. For example, you could define -- unionWithKey, differenceWithKey and -- intersectionWithKey as -- --
--   myUnionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) id id m1 m2
--   myDifferenceWithKey f m1 m2 = mergeWithKey f id (const empty) m1 m2
--   myIntersectionWithKey f m1 m2 = mergeWithKey (\k x1 x2 -> Just (f k x1 x2)) (const empty) (const empty) m1 m2
--   
-- -- When calling mergeWithKey combine only1 only2, a -- function combining two IntMaps is created, such that -- -- -- -- The only1 and only2 methods must return a map -- with a subset (possibly empty) of the keys of the given map. The -- values can be modified arbitrarily. Most common variants of -- only1 and only2 are id and const -- empty, but for example map f or -- filterWithKey f could be used for any f. mergeWithKey :: (Key -> a -> b -> Maybe c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c) -> IntMap a -> IntMap b -> IntMap c -- | O(n). Map a function over all values in the map. -- --
--   map (++ "x") (fromList [(5,"a"), (3,"b")]) == fromList [(3, "bx"), (5, "ax")]
--   
map :: (a -> b) -> IntMap a -> IntMap b -- | O(n). Map a function over all values in the map. -- --
--   let f key x = (show key) ++ ":" ++ x
--   mapWithKey f (fromList [(5,"a"), (3,"b")]) == fromList [(3, "3:b"), (5, "5:a")]
--   
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b -- | O(n). traverseWithKey f s == fromList -- $ traverse ((k, v) -> (,) k $ f k v) -- (toList m) That is, behaves exactly like a regular -- traverse except that the traversing function also has access to -- the key associated with a value. -- --
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(1, 'a'), (5, 'e')]) == Just (fromList [(1, 'b'), (5, 'f')])
--   traverseWithKey (\k v -> if odd k then Just (succ v) else Nothing) (fromList [(2, 'c')])           == Nothing
--   
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b) -- | O(n). Traverse keys/values and collect the Just results. traverseMaybeWithKey :: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b) -- | O(n). The function mapAccum threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a b = (a ++ b, b ++ "X")
--   mapAccum f "Everything: " (fromList [(5,"a"), (3,"b")]) == ("Everything: ba", fromList [(3, "bX"), (5, "aX")])
--   
mapAccum :: (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumWithKey threads an -- accumulating argument through the map in ascending order of keys. -- --
--   let f a k b = (a ++ " " ++ (show k) ++ "-" ++ b, b ++ "X")
--   mapAccumWithKey f "Everything:" (fromList [(5,"a"), (3,"b")]) == ("Everything: 3-b 5-a", fromList [(3, "bX"), (5, "aX")])
--   
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n). The function mapAccumRWithKey threads an -- accumulating argument through the map in descending order of keys. mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c) -- | O(n*min(n,W)). mapKeys f s is the map obtained -- by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the value at the -- greatest of the original keys is retained. -- --
--   mapKeys (+ 1) (fromList [(5,"a"), (3,"b")])                        == fromList [(4, "b"), (6, "a")]
--   mapKeys (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "c"
--   mapKeys (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "c"
--   
mapKeys :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysWith c f s is the map -- obtained by applying f to each key of s. -- -- The size of the result may be smaller if f maps two or more -- distinct keys to the same new key. In this case the associated values -- will be combined using c. -- --
--   mapKeysWith (++) (\ _ -> 1) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 1 "cdab"
--   mapKeysWith (++) (\ _ -> 3) (fromList [(1,"b"), (2,"a"), (3,"d"), (4,"c")]) == singleton 3 "cdab"
--   
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> IntMap a -> IntMap a -- | O(n*min(n,W)). mapKeysMonotonic f s == -- mapKeys f s, but works only when f is strictly -- monotonic. That is, for any values x and y, if -- x < y then f x < f y. The -- precondition is not checked. Semi-formally, we have: -- --
--   and [x < y ==> f x < f y | x <- ls, y <- ls]
--                       ==> mapKeysMonotonic f s == mapKeys f s
--       where ls = keys s
--   
-- -- This means that f maps distinct original keys to distinct -- resulting keys. This function has slightly better performance than -- mapKeys. -- --
--   mapKeysMonotonic (\ k -> k * 2) (fromList [(5,"a"), (3,"b")]) == fromList [(6, "b"), (10, "a")]
--   
mapKeysMonotonic :: (Key -> Key) -> IntMap a -> IntMap a -- | O(n). Fold the values in the map using the given -- right-associative binary operator, such that foldr f z == -- foldr f z . elems. -- -- For example, -- --
--   elems map = foldr (:) [] map
--   
-- --
--   let f a len = len + (length a)
--   foldr f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldr :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the values in the map using the given -- left-associative binary operator, such that foldl f z == -- foldl f z . elems. -- -- For example, -- --
--   elems = reverse . foldl (flip (:)) []
--   
-- --
--   let f len a = len + (length a)
--   foldl f 0 (fromList [(5,"a"), (3,"bbb")]) == 4
--   
foldl :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- right-associative binary operator, such that foldrWithKey f -- z == foldr (uncurry f) z . toAscList. -- -- For example, -- --
--   keys map = foldrWithKey (\k x ks -> k:ks) [] map
--   
-- --
--   let f k a result = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldrWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (5:a)(3:b)"
--   
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). Fold the keys and values in the map using the given -- left-associative binary operator, such that foldlWithKey f -- z == foldl (\z' (kx, x) -> f z' kx x) z . -- toAscList. -- -- For example, -- --
--   keys = reverse . foldlWithKey (\ks k x -> k:ks) []
--   
-- --
--   let f result k a = result ++ "(" ++ (show k) ++ ":" ++ a ++ ")"
--   foldlWithKey f "Map: " (fromList [(5,"a"), (3,"b")]) == "Map: (3:b)(5:a)"
--   
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Fold the keys and values in the map using the given -- monoid, such that -- --
--   foldMapWithKey f = fold . mapWithKey f
--   
-- -- This can be an asymptotically faster than foldrWithKey or -- foldlWithKey for some monoids. foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m -- | O(n). A strict version of foldr. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldr' :: (a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldl. Each application of the -- operator is evaluated before using the result in the next application. -- This function is strict in the starting value. foldl' :: (a -> b -> a) -> a -> IntMap b -> a -- | O(n). A strict version of foldrWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b -- | O(n). A strict version of foldlWithKey. Each application -- of the operator is evaluated before using the result in the next -- application. This function is strict in the starting value. foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a -- | O(n). Return all elements of the map in the ascending order of -- their keys. Subject to list fusion. -- --
--   elems (fromList [(5,"a"), (3,"b")]) == ["b","a"]
--   elems empty == []
--   
elems :: IntMap a -> [a] -- | O(n). Return all keys of the map in ascending order. Subject to -- list fusion. -- --
--   keys (fromList [(5,"a"), (3,"b")]) == [3,5]
--   keys empty == []
--   
keys :: IntMap a -> [Key] -- | O(n). An alias for toAscList. Returns all key/value -- pairs in the map in ascending key order. Subject to list fusion. -- --
--   assocs (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   assocs empty == []
--   
assocs :: IntMap a -> [(Key, a)] -- | O(n*min(n,W)). The set of all keys of the map. -- --
--   keysSet (fromList [(5,"a"), (3,"b")]) == Data.IntSet.fromList [3,5]
--   keysSet empty == Data.IntSet.empty
--   
keysSet :: IntMap a -> IntSet -- | O(n). Convert the map to a list of key/value pairs. Subject to -- list fusion. -- --
--   toList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   toList empty == []
--   
toList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in ascending order. Subject to list fusion. -- --
--   toAscList (fromList [(5,"a"), (3,"b")]) == [(3,"b"), (5,"a")]
--   
toAscList :: IntMap a -> [(Key, a)] -- | O(n). Convert the map to a list of key/value pairs where the -- keys are in descending order. Subject to list fusion. -- --
--   toDescList (fromList [(5,"a"), (3,"b")]) == [(5,"a"), (3,"b")]
--   
toDescList :: IntMap a -> [(Key, a)] -- | O(n). Filter all values that satisfy some predicate. -- --
--   filter (> "a") (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   filter (> "x") (fromList [(5,"a"), (3,"b")]) == empty
--   filter (< "a") (fromList [(5,"a"), (3,"b")]) == empty
--   
filter :: (a -> Bool) -> IntMap a -> IntMap a -- | O(n). Filter all keys/values that satisfy some predicate. -- --
--   filterWithKey (\k _ -> k > 4) (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a -- | O(n+m). The restriction of a map to the keys in a set. -- --
--   m `restrictKeys` s = filterWithKey (k _ -> k `member` s) m
--   
restrictKeys :: IntMap a -> IntSet -> IntMap a -- | O(n+m). Remove all the keys in a given set from a map. -- --
--   m `withoutKeys` s = filterWithKey (k _ -> k `notMember` s) m
--   
withoutKeys :: IntMap a -> IntSet -> IntMap a -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partition (> "a") (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   partition (< "x") (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partition (> "x") (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Partition the map according to some predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also split. -- --
--   partitionWithKey (\ k _ -> k > 3) (fromList [(5,"a"), (3,"b")]) == (singleton 5 "a", singleton 3 "b")
--   partitionWithKey (\ k _ -> k < 7) (fromList [(5,"a"), (3,"b")]) == (fromList [(3, "b"), (5, "a")], empty)
--   partitionWithKey (\ k _ -> k > 7) (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3, "b"), (5, "a")])
--   
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a) -- | O(n). Map values and collect the Just results. -- --
--   let f x = if x == "a" then Just "new a" else Nothing
--   mapMaybe f (fromList [(5,"a"), (3,"b")]) == singleton 5 "new a"
--   
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map keys/values and collect the Just results. -- --
--   let f k _ = if k < 5 then Just ("key : " ++ (show k)) else Nothing
--   mapMaybeWithKey f (fromList [(5,"a"), (3,"b")]) == singleton 3 "key : 3"
--   
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b -- | O(n). Map values and separate the Left and Right -- results. -- --
--   let f a = if a < "c" then Left a else Right a
--   mapEither f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(3,"b"), (5,"a")], fromList [(1,"x"), (7,"z")])
--   
--   mapEither (\ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--   
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(n). Map keys/values and separate the Left and -- Right results. -- --
--   let f k a = if k < 5 then Left (k * 2) else Right (a ++ a)
--   mapEitherWithKey f (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (fromList [(1,2), (3,6)], fromList [(5,"aa"), (7,"zz")])
--   
--   mapEitherWithKey (\_ a -> Right a) (fromList [(5,"a"), (3,"b"), (1,"x"), (7,"z")])
--       == (empty, fromList [(1,"x"), (3,"b"), (5,"a"), (7,"z")])
--   
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c) -- | O(min(n,W)). The expression (split k map) is a -- pair (map1,map2) where all keys in map1 are lower -- than k and all keys in map2 larger than k. -- Any key equal to k is found in neither map1 nor -- map2. -- --
--   split 2 (fromList [(5,"a"), (3,"b")]) == (empty, fromList [(3,"b"), (5,"a")])
--   split 3 (fromList [(5,"a"), (3,"b")]) == (empty, singleton 5 "a")
--   split 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", singleton 5 "a")
--   split 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", empty)
--   split 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], empty)
--   
split :: Key -> IntMap a -> (IntMap a, IntMap a) -- | O(min(n,W)). Performs a split but also returns whether -- the pivot key was found in the original map. -- --
--   splitLookup 2 (fromList [(5,"a"), (3,"b")]) == (empty, Nothing, fromList [(3,"b"), (5,"a")])
--   splitLookup 3 (fromList [(5,"a"), (3,"b")]) == (empty, Just "b", singleton 5 "a")
--   splitLookup 4 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Nothing, singleton 5 "a")
--   splitLookup 5 (fromList [(5,"a"), (3,"b")]) == (singleton 3 "b", Just "a", empty)
--   splitLookup 6 (fromList [(5,"a"), (3,"b")]) == (fromList [(3,"b"), (5,"a")], Nothing, empty)
--   
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a) -- | O(1). Decompose a map into pieces based on the structure of the -- underlying tree. This function is useful for consuming a map in -- parallel. -- -- No guarantee is made as to the sizes of the pieces; an internal, but -- deterministic process determines this. However, it is guaranteed that -- the pieces returned will be in ascending order (all elements in the -- first submap less than all elements in the second, and so on). -- -- Examples: -- --
--   splitRoot (fromList (zip [1..6::Int] ['a'..])) ==
--     [fromList [(1,'a'),(2,'b'),(3,'c')],fromList [(4,'d'),(5,'e'),(6,'f')]]
--   
-- --
--   splitRoot empty == []
--   
-- -- Note that the current implementation does not return more than two -- submaps, but you should not depend on this behaviour because it can -- change in the future without notice. splitRoot :: IntMap a -> [IntMap a] -- | O(n+m). Is this a submap? Defined as (isSubmapOf = -- isSubmapOfBy (==)). isSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). The expression (isSubmapOfBy f m1 m2) -- returns True if all keys in m1 are in m2, and -- when f returns True when applied to their respective -- values. For example, the following expressions are all True: -- --
--   isSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isSubmapOfBy (==) (fromList [(1,2)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (<) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- Defined as (isProperSubmapOf = isProperSubmapOfBy -- (==)). isProperSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool -- | O(n+m). Is this a proper submap? (ie. a submap but not equal). -- The expression (isProperSubmapOfBy f m1 m2) returns -- True when keys m1 and keys m2 are not equal, -- all keys in m1 are in m2, and when f -- returns True when applied to their respective values. For -- example, the following expressions are all True: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (<=) (fromList [(1,1)]) (fromList [(1,1),(2,2)])
--   
-- -- But the following are all False: -- --
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1),(2,2)])
--   isProperSubmapOfBy (==) (fromList [(1,1),(2,2)]) (fromList [(1,1)])
--   isProperSubmapOfBy (<)  (fromList [(1,1)])       (fromList [(1,1),(2,2)])
--   
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool -- | O(min(n,W)). The minimal key of the map. Returns Nothing -- if the map is empty. lookupMin :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The maximal key of the map. Returns Nothing -- if the map is empty. lookupMax :: IntMap a -> Maybe (Key, a) -- | O(min(n,W)). The minimal key of the map. Calls error if -- the map is empty. Use minViewWithKey if the map may be empty. findMin :: IntMap a -> (Key, a) -- | O(min(n,W)). The maximal key of the map. Calls error if -- the map is empty. Use maxViewWithKey if the map may be empty. findMax :: IntMap a -> (Key, a) -- | O(min(n,W)). Delete the minimal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMin :: IntMap a -> IntMap a -- | O(min(n,W)). Delete the maximal key. Returns an empty map if -- the map is empty. -- -- Note that this is a change of behaviour for consistency with -- Map – versions prior to 0.5 threw an error if the IntMap -- was already empty. deleteMax :: IntMap a -> IntMap a -- | O(min(n,W)). Delete and find the minimal element. This function -- throws an error if the map is empty. Use minViewWithKey if the -- map may be empty. deleteFindMin :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Delete and find the maximal element. This function -- throws an error if the map is empty. Use maxViewWithKey if the -- map may be empty. deleteFindMax :: IntMap a -> ((Key, a), IntMap a) -- | O(min(n,W)). Update the value at the minimal key. -- --
--   updateMin (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "Xb"), (5, "a")]
--   updateMin (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the maximal key. -- --
--   updateMax (\ a -> Just ("X" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3, "b"), (5, "Xa")]
--   updateMax (\ _ -> Nothing)         (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the minimal key. -- --
--   updateMinWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"3:b"), (5,"a")]
--   updateMinWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 5 "a"
--   
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Update the value at the maximal key. -- --
--   updateMaxWithKey (\ k a -> Just ((show k) ++ ":" ++ a)) (fromList [(5,"a"), (3,"b")]) == fromList [(3,"b"), (5,"5:a")]
--   updateMaxWithKey (\ _ _ -> Nothing)                     (fromList [(5,"a"), (3,"b")]) == singleton 3 "b"
--   
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a -- | O(min(n,W)). Retrieves the minimal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. minView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the maximal key of the map, and the map -- stripped of that element, or Nothing if passed an empty map. maxView :: IntMap a -> Maybe (a, IntMap a) -- | O(min(n,W)). Retrieves the minimal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   minViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((3,"b"), singleton 5 "a")
--   minViewWithKey empty == Nothing
--   
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | O(min(n,W)). Retrieves the maximal (key,value) pair of the map, -- and the map stripped of that element, or Nothing if passed an -- empty map. -- --
--   maxViewWithKey (fromList [(5,"a"), (3,"b")]) == Just ((5,"a"), singleton 3 "b")
--   maxViewWithKey empty == Nothing
--   
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a) -- | showTree has moved to showTree showTree :: Whoops "Data.IntMap.showTree has moved to Data.IntMap.Internal.Debug.showTree" => IntMap a -> String -- | showTreeWith has moved to showTreeWith showTreeWith :: Whoops "Data.IntMap.showTreeWith has moved to Data.IntMap.Internal.Debug.showTreeWith" => Bool -> Bool -> IntMap a -> String -- | An efficient implementation of maps from integer keys to values -- (dictionaries). -- -- This module re-exports the value lazy Data.IntMap.Lazy API, -- plus several deprecated value strict functions. Please note that these -- functions have different strictness properties than those in -- Data.IntMap.Strict: they only evaluate the result of the -- combining function. For example, the default value to -- insertWith' is only evaluated if the combining function is -- called and uses it. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import Data.IntMap (IntMap)
--   import qualified Data.IntMap as IntMap
--   
-- -- The implementation is based on big-endian patricia trees. This -- data structure performs especially well on binary operations like -- union and intersection. However, my benchmarks show that -- it is also (much) faster on insertions and deletions when compared to -- a generic size-balanced map implementation (see Data.Map). -- -- -- -- Operation comments contain the operation time complexity in the Big-O -- notation http://en.wikipedia.org/wiki/Big_O_notation. Many -- operations have a worst-case complexity of O(min(n,W)). This -- means that the operation can become linear in the number of elements -- with a maximum of W -- the number of bits in an Int (32 -- or 64). module Data.IntMap -- | This function is being removed and is no longer usable. Use -- insertWith insertWith' :: Whoops "Data.IntMap.insertWith' is gone. Use Data.IntMap.Strict.insertWith." => (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | This function is being removed and is no longer usable. Use -- insertWithKey. insertWithKey' :: Whoops "Data.IntMap.insertWithKey' is gone. Use Data.IntMap.Strict.insertWithKey." => (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a -- | This function is being removed and is no longer usable. Use -- foldr. fold :: Whoops "Data.IntMap.fold' is gone. Use Data.IntMap.foldr or Prelude.foldr." => (a -> b -> b) -> b -> IntMap a -> b -- | This function is being removed and is no longer usable. Use -- foldrWithKey. foldWithKey :: Whoops "Data.IntMap.foldWithKey is gone. Use foldrWithKey." => (Key -> a -> b -> b) -> b -> IntMap a -> b