@@ -137,17 +137,11 @@ module Data.HashMap.Internal
137137 , adjust #
138138 ) where
139139
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)
147141import Data.Semigroup (Semigroup ((<>) ))
148142#endif
149143import Control.DeepSeq (NFData (rnf ))
150- import Control.Monad.ST (ST )
144+ import Control.Monad.ST (ST , runST )
151145import Data.Bits ((.&.) , (.|.) , complement , popCount , unsafeShiftL , unsafeShiftR )
152146import Data.Data hiding (Typeable )
153147import qualified Data.Foldable as Foldable
@@ -162,17 +156,14 @@ import Text.Read hiding (step)
162156import qualified Data.HashMap.Internal.Array as A
163157import qualified Data.Hashable as H
164158import Data.Hashable (Hashable )
165- import Data.HashMap.Internal.Unsafe (runST )
166159import Data.HashMap.Internal.List (isPermutationBy , unorderedCompare )
167160import Data.Typeable (Typeable )
168161
169162import GHC.Exts (isTrue #)
170163import qualified GHC.Exts as Exts
171164
172- #if MIN_VERSION_base(4,9,0)
173165import Data.Functor.Classes
174166import GHC.Stack
175- #endif
176167
177168#if MIN_VERSION_hashable(1,2,5)
178169import qualified Data.Hashable.Lifted as H
@@ -186,9 +177,7 @@ import qualified Control.DeepSeq as NF
186177import GHC.Exts (TYPE , Int (.. ), Int #)
187178#endif
188179
189- #if MIN_VERSION_base(4,8,0)
190180import Data.Functor.Identity (Identity (.. ))
191- #endif
192181import Control.Applicative (Const (.. ))
193182import Data.Coerce (coerce )
194183
@@ -265,12 +254,10 @@ instance Foldable.Foldable (HashMap k) where
265254 {-# INLINE foldr' #-}
266255 foldl' = foldl'
267256 {-# INLINE foldl' #-}
268- #if MIN_VERSION_base(4,8,0)
269257 null = null
270258 {-# INLINE null #-}
271259 length = size
272260 {-# INLINE length #-}
273- #endif
274261
275262#if MIN_VERSION_base(4,10,0)
276263-- | @since 0.2.11
@@ -283,7 +270,6 @@ instance Bifoldable HashMap where
283270 {-# INLINE bifoldl #-}
284271#endif
285272
286- #if __GLASGOW_HASKELL__ >= 711
287273-- | '<>' = 'union'
288274--
289275-- 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
295281instance (Eq k , Hashable k ) => Semigroup (HashMap k v ) where
296282 (<>) = union
297283 {-# INLINE (<>) #-}
298- #endif
299284
300285-- | 'mempty' = 'empty'
301286--
@@ -310,11 +295,7 @@ instance (Eq k, Hashable k) => Semigroup (HashMap k v) where
310295instance (Eq k , Hashable k ) => Monoid (HashMap k v ) where
311296 mempty = empty
312297 {-# INLINE mempty #-}
313- #if __GLASGOW_HASKELL__ >= 711
314298 mappend = (<>)
315- #else
316- mappend = union
317- #endif
318299 {-# INLINE mappend #-}
319300
320301instance (Data k , Data v , Eq k , Hashable k ) => Data (HashMap k v ) where
@@ -336,7 +317,6 @@ type Hash = Word
336317type Bitmap = Word
337318type Shift = Int
338319
339- #if MIN_VERSION_base(4,9,0)
340320instance Show2 HashMap where
341321 liftShowsPrec2 spk slk spv slv d m =
342322 showsUnaryWith (liftShowsPrec sp sl) " fromList" d (toList m)
@@ -353,7 +333,6 @@ instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
353333 where
354334 rp' = liftReadsPrec rp rl
355335 rl' = liftReadList rp rl
356- #endif
357336
358337instance (Eq k , Hashable k , Read k , Read e ) => Read (HashMap k e ) where
359338 readPrec = parens $ prec 10 $ do
@@ -371,13 +350,11 @@ instance Traversable (HashMap k) where
371350 traverse f = traverseWithKey (const f)
372351 {-# INLINABLE traverse #-}
373352
374- #if MIN_VERSION_base(4,9,0)
375353instance Eq2 HashMap where
376354 liftEq2 = equal2
377355
378356instance Eq k => Eq1 (HashMap k ) where
379357 liftEq = equal1
380- #endif
381358
382359-- | Note that, in the presence of hash collisions, equal @HashMap@s may
383360-- behave differently, i.e. substitutivity may be violated:
@@ -441,13 +418,11 @@ equal2 eqk eqv t1 t2 = go (toList' t1 []) (toList' t2 [])
441418
442419 leafEq (L k v) (L k' v') = eqk k k' && eqv v v'
443420
444- #if MIN_VERSION_base(4,9,0)
445421instance Ord2 HashMap where
446422 liftCompare2 = cmp
447423
448424instance Ord k => Ord1 (HashMap k ) where
449425 liftCompare = cmp compare
450- #endif
451426
452427-- | The ordering is total and consistent with the `Eq` instance. However,
453428-- nothing else about the ordering is specified, and it may change from
@@ -775,11 +750,7 @@ lookupDefault def k t = findWithDefault def k t
775750
776751-- | /O(log n)/ Return the value to which the specified key is mapped.
777752-- Calls 'error' if this map contains no mapping for the key.
778- #if MIN_VERSION_base(4,9,0)
779753(!) :: (Eq k , Hashable k , HasCallStack ) => HashMap k v -> k -> v
780- #else
781- (!) :: (Eq k , Hashable k ) => HashMap k v -> k -> v
782- #endif
783754(!) m k = case lookup k m of
784755 Just v -> v
785756 Nothing -> error " Data.HashMap.Internal.(!): key not found"
@@ -1331,7 +1302,6 @@ alterF f = \ !k !m ->
13311302-- rule from firing.
13321303{-# INLINABLE [0] alterF #-}
13331304
1334- #if MIN_VERSION_base(4,8,0)
13351305-- This is just a bottom value. See the comment on the "alterFWeird"
13361306-- rule.
13371307test_bottom :: a
@@ -1448,7 +1418,6 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
14481418 Absent -> Nothing
14491419 Present v _ -> Just v
14501420{-# INLINABLE alterFEager #-}
1451- #endif
14521421
14531422-- | /O(n*log m)/ Inclusion of maps. A map is included in another map if the keys
14541423-- are subsets and the corresponding values are equal:
0 commit comments