1010{-# LANGUAGE TemplateHaskellQuotes #-}
1111{-# LANGUAGE TypeFamilies #-}
1212{-# LANGUAGE UnboxedTuples #-}
13- #if __GLASGOW_HASKELL__ >= 802
1413{-# LANGUAGE TypeInType #-}
1514{-# LANGUAGE UnboxedSums #-}
16- #endif
1715{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
1816{-# OPTIONS_HADDOCK not-home #-}
1917
@@ -148,9 +146,7 @@ import Control.Monad.ST (ST, runST)
148146import Data.Bits ((.&.) , (.|.) , complement , popCount , unsafeShiftL , unsafeShiftR )
149147import Data.Data
150148import qualified Data.Foldable as Foldable
151- #if MIN_VERSION_base(4,10,0)
152149import Data.Bifoldable
153- #endif
154150import qualified Data.List as L
155151import GHC.Exts ((==#) , build , reallyUnsafePtrEquality #, inline )
156152import Prelude hiding (filter , foldl , foldr , lookup , map , null , pred )
@@ -171,13 +167,9 @@ import GHC.Stack
171167import qualified Data.Hashable.Lifted as H
172168#endif
173169
174- #if MIN_VERSION_deepseq(1,4,3)
175170import qualified Control.DeepSeq as NF
176- #endif
177171
178- #if __GLASGOW_HASKELL__ >= 802
179172import GHC.Exts (TYPE , Int (.. ), Int #)
180- #endif
181173
182174import Data.Functor.Identity (Identity (.. ))
183175import Control.Applicative (Const (.. ))
@@ -205,15 +197,13 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
205197 lift (L k v) = [| L k $! v | ]
206198#endif
207199
208- #if MIN_VERSION_deepseq(1,4,3)
209200-- | @since 0.2.14.0
210201instance NFData k => NF. NFData1 (Leaf k ) where
211202 liftRnf rnf2 = NF. liftRnf2 rnf rnf2
212203
213204-- | @since 0.2.14.0
214205instance NF. NFData2 Leaf where
215206 liftRnf2 rnf1 rnf2 (L k v) = rnf1 k `seq` rnf2 v
216- #endif
217207
218208-- Invariant: The length of the 1st argument to 'Full' is
219209-- 2^bitsPerSubkey
@@ -239,7 +229,6 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
239229 rnf (Full ary) = rnf ary
240230 rnf (Collision _ ary) = rnf ary
241231
242- #if MIN_VERSION_deepseq(1,4,3)
243232-- | @since 0.2.14.0
244233instance NFData k => NF. NFData1 (HashMap k ) where
245234 liftRnf rnf2 = NF. liftRnf2 rnf rnf2
@@ -251,7 +240,6 @@ instance NF.NFData2 HashMap where
251240 liftRnf2 rnf1 rnf2 (Leaf _ l) = NF. liftRnf2 rnf1 rnf2 l
252241 liftRnf2 rnf1 rnf2 (Full ary) = NF. liftRnf (NF. liftRnf2 rnf1 rnf2) ary
253242 liftRnf2 rnf1 rnf2 (Collision _ ary) = NF. liftRnf (NF. liftRnf2 rnf1 rnf2) ary
254- #endif
255243
256244instance Functor (HashMap k ) where
257245 fmap = map
@@ -272,7 +260,6 @@ instance Foldable.Foldable (HashMap k) where
272260 length = size
273261 {-# INLINE length #-}
274262
275- #if MIN_VERSION_base(4,10,0)
276263-- | @since 0.2.11
277264instance Bifoldable HashMap where
278265 bifoldMap f g = foldMapWithKey (\ k v -> f k `mappend` g v)
@@ -281,7 +268,6 @@ instance Bifoldable HashMap where
281268 {-# INLINE bifoldr #-}
282269 bifoldl f g = foldlWithKey (\ acc k v -> (acc `f` k) `g` v)
283270 {-# INLINE bifoldl #-}
284- #endif
285271
286272-- | '<>' = 'union'
287273--
@@ -606,7 +592,6 @@ member k m = case lookup k m of
606592-- | /O(log n)/ Return the value to which the specified key is mapped,
607593-- or 'Nothing' if this map contains no mapping for the key.
608594lookup :: (Eq k , Hashable k ) => k -> HashMap k v -> Maybe v
609- #if __GLASGOW_HASKELL__ >= 802
610595-- GHC does not yet perform a worker-wrapper transformation on
611596-- unboxed sums automatically. That seems likely to happen at some
612597-- point (possibly as early as GHC 8.6) but for now we do it manually.
@@ -619,16 +604,9 @@ lookup# :: (Eq k, Hashable k) => k -> HashMap k v -> (# (# #) | v #)
619604lookup # k m = lookupCont (\ _ -> (# (# # ) | # )) (\ v _i -> (# | v # )) (hash k) k 0 m
620605{-# INLINABLE lookup# #-}
621606
622- #else
623-
624- lookup k m = lookupCont (\ _ -> Nothing ) (\ v _i -> Just v) (hash k) k 0 m
625- {-# INLINABLE lookup #-}
626- #endif
627-
628607-- | lookup' is a version of lookup that takes the hash separately.
629608-- It is used to implement alterF.
630609lookup' :: Eq k => Hash -> k -> HashMap k v -> Maybe v
631- #if __GLASGOW_HASKELL__ >= 802
632610-- GHC does not yet perform a worker-wrapper transformation on
633611-- unboxed sums automatically. That seems likely to happen at some
634612-- point (possibly as early as GHC 8.6) but for now we do it manually.
@@ -639,10 +617,6 @@ lookup' h k m = case lookupRecordCollision# h k m of
639617 (# (# # ) | # ) -> Nothing
640618 (# | (# a, _i # ) # ) -> Just a
641619{-# INLINE lookup' #-}
642- #else
643- lookup' h k m = lookupCont (\ _ -> Nothing ) (\ v _i -> Just v) h k 0 m
644- {-# INLINABLE lookup' #-}
645- #endif
646620
647621-- The result of a lookup, keeping track of if a hash collision occured.
648622-- If a collision did not occur then it will have the Int value (-1).
@@ -662,7 +636,6 @@ data LookupRes a = Absent | Present a !Int
662636-- Key in map, no collision => Present v (-1)
663637-- Key in map, collision => Present v position
664638lookupRecordCollision :: Eq k => Hash -> k -> HashMap k v -> LookupRes v
665- #if __GLASGOW_HASKELL__ >= 802
666639lookupRecordCollision h k m = case lookupRecordCollision# h k m of
667640 (# (# # ) | # ) -> Absent
668641 (# | (# a, i # ) # ) -> Present a (I # i) -- GHC will eliminate the I#
@@ -679,12 +652,6 @@ lookupRecordCollision# h k m =
679652-- INLINABLE to specialize to the Eq instance.
680653{-# INLINABLE lookupRecordCollision# #-}
681654
682- #else /* GHC < 8.2 so there are no unboxed sums */
683-
684- lookupRecordCollision h k m = lookupCont (\ _ -> Absent ) Present h k 0 m
685- {-# INLINABLE lookupRecordCollision #-}
686- #endif
687-
688655-- A two-continuation version of lookupRecordCollision. This lets us
689656-- share source code between lookup and lookupRecordCollision without
690657-- risking any performance degradation.
@@ -698,11 +665,7 @@ lookupRecordCollision h k m = lookupCont (\_ -> Absent) Present h k 0 m
698665-- keys at the top-level of a hashmap, the offset should be 0. When looking up
699666-- keys at level @n@ of a hashmap, the offset should be @n * bitsPerSubkey@.
700667lookupCont ::
701- #if __GLASGOW_HASKELL__ >= 802
702668 forall rep (r :: TYPE rep ) k v .
703- #else
704- forall r k v.
705- #endif
706669 Eq k
707670 => ((# # ) -> r ) -- Absent continuation
708671 -> (v -> Int -> r ) -- Present continuation
@@ -2155,11 +2118,7 @@ fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty
21552118-- | /O(n)/ Look up the value associated with the given key in an
21562119-- array.
21572120lookupInArrayCont ::
2158- #if __GLASGOW_HASKELL__ >= 802
21592121 forall rep (r :: TYPE rep ) k v .
2160- #else
2161- forall r k v.
2162- #endif
21632122 Eq k => ((# # ) -> r ) -> (v -> Int -> r ) -> k -> A. Array (Leaf k v ) -> r
21642123lookupInArrayCont absent present k0 ary0 = go k0 ary0 0 (A. length ary0)
21652124 where
0 commit comments