File: Map.hs

package info (click to toggle)
ghc 8.0.1-17
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 55,080 kB
  • ctags: 9,332
  • sloc: haskell: 363,120; ansic: 54,900; sh: 4,782; makefile: 974; perl: 542; asm: 315; python: 306; xml: 154; lisp: 7
file content (136 lines) | stat: -rw-r--r-- 4,530 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
{-# LANGUAGE CPP #-}
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Safe #-}
#endif

#include "containers.h"

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Map
-- Copyright   :  (c) Daan Leijen 2002
--                (c) Andriy Palamarchuk 2008
-- License     :  BSD-style
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- /Note:/ You should use "Data.Map.Strict" instead of this module if:
--
-- * You will eventually need all the values stored.
--
-- * The stored values don't represent large virtual data structures
-- to be lazily computed.
--
-- 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:
--
--    * Stephen Adams, \"/Efficient sets: a balancing act/\",
--     Journal of Functional Programming 3(4):553-562, October 1993,
--     <http://www.swiss.ai.mit.edu/~adams/BB/>.
--
--    * J. Nievergelt and E.M. Reingold,
--      \"/Binary search trees of bounded balance/\",
--      SIAM journal of computing 2(1), March 1973.
--
-- 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
    ( module Data.Map.Lazy
    , insertWith'
    , insertWithKey'
    , insertLookupWithKey'
    , fold
    , foldWithKey
    ) where

import Prelude hiding (foldr)
import Data.Map.Lazy
import qualified Data.Map.Strict as Strict

-- | /Deprecated./ As of version 0.5, replaced by 'Data.Map.Strict.insertWith'.
--
-- /O(log n)/. Same as 'insertWith', but the value being inserted to the map is
-- evaluated to WHNF beforehand.
--
-- For example, to update a counter:
--
-- > insertWith' (+) k 1 m
--

insertWith' :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWith' = Strict.insertWith
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE insertWith' #-}
#else
{-# INLINE insertWith' #-}
#endif

-- | /Deprecated./ As of version 0.5, replaced by
-- 'Data.Map.Strict.insertWithKey'.
--
-- /O(log n)/. Same as 'insertWithKey', but the value being inserted to the map is
-- evaluated to WHNF beforehand.

insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
-- We do not reuse Data.Map.Strict.insertWithKey, because it is stricter -- it
-- forces evaluation of the given value.
insertWithKey' = Strict.insertWithKey
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE insertWithKey' #-}
#else
{-# INLINE insertWithKey' #-}
#endif

-- | /Deprecated./ As of version 0.5, replaced by
-- 'Data.Map.Strict.insertLookupWithKey'.
--
-- /O(log n)/. Same as 'insertLookupWithKey', but the value being inserted to
-- the map is evaluated to WHNF beforehand.

insertLookupWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a
                     -> (Maybe a, Map k a)
-- We do not reuse Data.Map.Strict.insertLookupWithKey, because it is stricter -- it
-- forces evaluation of the given value.
insertLookupWithKey' = Strict.insertLookupWithKey
#if __GLASGOW_HASKELL__ >= 700
{-# INLINABLE insertLookupWithKey' #-}
#else
{-# INLINE insertLookupWithKey' #-}
#endif

-- | /Deprecated./ As of version 0.5, replaced by 'foldr'.
--
-- /O(n)/. Fold the values in the map using the given right-associative
-- binary operator. This function is an equivalent of 'foldr' and is present
-- for compatibility only.
fold :: (a -> b -> b) -> b -> Map k a -> b
fold = foldr
{-# INLINE fold #-}

-- | /Deprecated./ As of version 0.4, replaced by 'foldrWithKey'.
--
-- /O(n)/. Fold the keys and values in the map using the given right-associative
-- binary operator. This function is an equivalent of 'foldrWithKey' and is present
-- for compatibility only.
foldWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b
foldWithKey = foldrWithKey
{-# INLINE foldWithKey #-}