@@ -137,17 +137,11 @@ module Data.HashMap.Internal
137
137
, adjust #
138
138
) where
139
139
140
- #if __GLASGOW_HASKELL__ < 710
141
- import Control.Applicative ((<$>) , Applicative (pure ))
142
- import Data.Monoid (Monoid (mempty , mappend ))
143
- import Data.Traversable (Traversable (.. ))
144
- import Data.Word (Word )
145
- #endif
146
- #if __GLASGOW_HASKELL__ >= 711
140
+ #if !MIN_VERSION_base(4,11,0)
147
141
import Data.Semigroup (Semigroup ((<>) ))
148
142
#endif
149
143
import Control.DeepSeq (NFData (rnf ))
150
- import Control.Monad.ST (ST )
144
+ import Control.Monad.ST (ST , runST )
151
145
import Data.Bits ((.&.) , (.|.) , complement , popCount , unsafeShiftL , unsafeShiftR )
152
146
import Data.Data hiding (Typeable )
153
147
import qualified Data.Foldable as Foldable
@@ -162,17 +156,14 @@ import Text.Read hiding (step)
162
156
import qualified Data.HashMap.Internal.Array as A
163
157
import qualified Data.Hashable as H
164
158
import Data.Hashable (Hashable )
165
- import Data.HashMap.Internal.Unsafe (runST )
166
159
import Data.HashMap.Internal.List (isPermutationBy , unorderedCompare )
167
160
import Data.Typeable (Typeable )
168
161
169
162
import GHC.Exts (isTrue #)
170
163
import qualified GHC.Exts as Exts
171
164
172
- #if MIN_VERSION_base(4,9,0)
173
165
import Data.Functor.Classes
174
166
import GHC.Stack
175
- #endif
176
167
177
168
#if MIN_VERSION_hashable(1,2,5)
178
169
import qualified Data.Hashable.Lifted as H
@@ -186,9 +177,7 @@ import qualified Control.DeepSeq as NF
186
177
import GHC.Exts (TYPE , Int (.. ), Int #)
187
178
#endif
188
179
189
- #if MIN_VERSION_base(4,8,0)
190
180
import Data.Functor.Identity (Identity (.. ))
191
- #endif
192
181
import Control.Applicative (Const (.. ))
193
182
import Data.Coerce (coerce )
194
183
@@ -265,12 +254,10 @@ instance Foldable.Foldable (HashMap k) where
265
254
{-# INLINE foldr' #-}
266
255
foldl' = foldl'
267
256
{-# INLINE foldl' #-}
268
- #if MIN_VERSION_base(4,8,0)
269
257
null = null
270
258
{-# INLINE null #-}
271
259
length = size
272
260
{-# INLINE length #-}
273
- #endif
274
261
275
262
#if MIN_VERSION_base(4,10,0)
276
263
-- | @since 0.2.11
@@ -283,7 +270,6 @@ instance Bifoldable HashMap where
283
270
{-# INLINE bifoldl #-}
284
271
#endif
285
272
286
- #if __GLASGOW_HASKELL__ >= 711
287
273
-- | '<>' = 'union'
288
274
--
289
275
-- If a key occurs in both maps, the mapping from the first will be the mapping in the result.
@@ -295,7 +281,6 @@ instance Bifoldable HashMap where
295
281
instance (Eq k , Hashable k ) => Semigroup (HashMap k v ) where
296
282
(<>) = union
297
283
{-# INLINE (<>) #-}
298
- #endif
299
284
300
285
-- | 'mempty' = 'empty'
301
286
--
@@ -310,11 +295,7 @@ instance (Eq k, Hashable k) => Semigroup (HashMap k v) where
310
295
instance (Eq k , Hashable k ) => Monoid (HashMap k v ) where
311
296
mempty = empty
312
297
{-# INLINE mempty #-}
313
- #if __GLASGOW_HASKELL__ >= 711
314
298
mappend = (<>)
315
- #else
316
- mappend = union
317
- #endif
318
299
{-# INLINE mappend #-}
319
300
320
301
instance (Data k , Data v , Eq k , Hashable k ) => Data (HashMap k v ) where
@@ -336,7 +317,6 @@ type Hash = Word
336
317
type Bitmap = Word
337
318
type Shift = Int
338
319
339
- #if MIN_VERSION_base(4,9,0)
340
320
instance Show2 HashMap where
341
321
liftShowsPrec2 spk slk spv slv d m =
342
322
showsUnaryWith (liftShowsPrec sp sl) " fromList" d (toList m)
@@ -353,7 +333,6 @@ instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
353
333
where
354
334
rp' = liftReadsPrec rp rl
355
335
rl' = liftReadList rp rl
356
- #endif
357
336
358
337
instance (Eq k , Hashable k , Read k , Read e ) => Read (HashMap k e ) where
359
338
readPrec = parens $ prec 10 $ do
@@ -371,13 +350,11 @@ instance Traversable (HashMap k) where
371
350
traverse f = traverseWithKey (const f)
372
351
{-# INLINABLE traverse #-}
373
352
374
- #if MIN_VERSION_base(4,9,0)
375
353
instance Eq2 HashMap where
376
354
liftEq2 = equal2
377
355
378
356
instance Eq k => Eq1 (HashMap k ) where
379
357
liftEq = equal1
380
- #endif
381
358
382
359
-- | Note that, in the presence of hash collisions, equal @HashMap@s may
383
360
-- behave differently, i.e. substitutivity may be violated:
@@ -441,13 +418,11 @@ equal2 eqk eqv t1 t2 = go (toList' t1 []) (toList' t2 [])
441
418
442
419
leafEq (L k v) (L k' v') = eqk k k' && eqv v v'
443
420
444
- #if MIN_VERSION_base(4,9,0)
445
421
instance Ord2 HashMap where
446
422
liftCompare2 = cmp
447
423
448
424
instance Ord k => Ord1 (HashMap k ) where
449
425
liftCompare = cmp compare
450
- #endif
451
426
452
427
-- | The ordering is total and consistent with the `Eq` instance. However,
453
428
-- nothing else about the ordering is specified, and it may change from
@@ -775,11 +750,7 @@ lookupDefault def k t = findWithDefault def k t
775
750
776
751
-- | /O(log n)/ Return the value to which the specified key is mapped.
777
752
-- Calls 'error' if this map contains no mapping for the key.
778
- #if MIN_VERSION_base(4,9,0)
779
753
(!) :: (Eq k , Hashable k , HasCallStack ) => HashMap k v -> k -> v
780
- #else
781
- (!) :: (Eq k , Hashable k ) => HashMap k v -> k -> v
782
- #endif
783
754
(!) m k = case lookup k m of
784
755
Just v -> v
785
756
Nothing -> error " Data.HashMap.Internal.(!): key not found"
@@ -1331,7 +1302,6 @@ alterF f = \ !k !m ->
1331
1302
-- rule from firing.
1332
1303
{-# INLINABLE [0] alterF #-}
1333
1304
1334
- #if MIN_VERSION_base(4,8,0)
1335
1305
-- This is just a bottom value. See the comment on the "alterFWeird"
1336
1306
-- rule.
1337
1307
test_bottom :: a
@@ -1448,7 +1418,6 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
1448
1418
Absent -> Nothing
1449
1419
Present v _ -> Just v
1450
1420
{-# INLINABLE alterFEager #-}
1451
- #endif
1452
1421
1453
1422
-- | /O(n*log m)/ Inclusion of maps. A map is included in another map if the keys
1454
1423
-- are subsets and the corresponding values are equal:
0 commit comments