10
10
{-# LANGUAGE TemplateHaskellQuotes #-}
11
11
{-# LANGUAGE TypeFamilies #-}
12
12
{-# LANGUAGE UnboxedTuples #-}
13
- #if __GLASGOW_HASKELL__ >= 802
14
13
{-# LANGUAGE TypeInType #-}
15
14
{-# LANGUAGE UnboxedSums #-}
16
- #endif
17
15
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
18
16
{-# OPTIONS_HADDOCK not-home #-}
19
17
@@ -148,9 +146,7 @@ import Control.Monad.ST (ST, runST)
148
146
import Data.Bits ((.&.) , (.|.) , complement , popCount , unsafeShiftL , unsafeShiftR )
149
147
import Data.Data
150
148
import qualified Data.Foldable as Foldable
151
- #if MIN_VERSION_base(4,10,0)
152
149
import Data.Bifoldable
153
- #endif
154
150
import qualified Data.List as L
155
151
import GHC.Exts ((==#) , build , reallyUnsafePtrEquality #, inline )
156
152
import Prelude hiding (filter , foldl , foldr , lookup , map , null , pred )
@@ -171,13 +167,9 @@ import GHC.Stack
171
167
import qualified Data.Hashable.Lifted as H
172
168
#endif
173
169
174
- #if MIN_VERSION_deepseq(1,4,3)
175
170
import qualified Control.DeepSeq as NF
176
- #endif
177
171
178
- #if __GLASGOW_HASKELL__ >= 802
179
172
import GHC.Exts (TYPE , Int (.. ), Int #)
180
- #endif
181
173
182
174
import Data.Functor.Identity (Identity (.. ))
183
175
import Control.Applicative (Const (.. ))
@@ -205,15 +197,13 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
205
197
lift (L k v) = [| L k $! v | ]
206
198
#endif
207
199
208
- #if MIN_VERSION_deepseq(1,4,3)
209
200
-- | @since 0.2.14.0
210
201
instance NFData k => NF. NFData1 (Leaf k ) where
211
202
liftRnf rnf2 = NF. liftRnf2 rnf rnf2
212
203
213
204
-- | @since 0.2.14.0
214
205
instance NF. NFData2 Leaf where
215
206
liftRnf2 rnf1 rnf2 (L k v) = rnf1 k `seq` rnf2 v
216
- #endif
217
207
218
208
-- Invariant: The length of the 1st argument to 'Full' is
219
209
-- 2^bitsPerSubkey
@@ -239,7 +229,6 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
239
229
rnf (Full ary) = rnf ary
240
230
rnf (Collision _ ary) = rnf ary
241
231
242
- #if MIN_VERSION_deepseq(1,4,3)
243
232
-- | @since 0.2.14.0
244
233
instance NFData k => NF. NFData1 (HashMap k ) where
245
234
liftRnf rnf2 = NF. liftRnf2 rnf rnf2
@@ -251,7 +240,6 @@ instance NF.NFData2 HashMap where
251
240
liftRnf2 rnf1 rnf2 (Leaf _ l) = NF. liftRnf2 rnf1 rnf2 l
252
241
liftRnf2 rnf1 rnf2 (Full ary) = NF. liftRnf (NF. liftRnf2 rnf1 rnf2) ary
253
242
liftRnf2 rnf1 rnf2 (Collision _ ary) = NF. liftRnf (NF. liftRnf2 rnf1 rnf2) ary
254
- #endif
255
243
256
244
instance Functor (HashMap k ) where
257
245
fmap = map
@@ -272,7 +260,6 @@ instance Foldable.Foldable (HashMap k) where
272
260
length = size
273
261
{-# INLINE length #-}
274
262
275
- #if MIN_VERSION_base(4,10,0)
276
263
-- | @since 0.2.11
277
264
instance Bifoldable HashMap where
278
265
bifoldMap f g = foldMapWithKey (\ k v -> f k `mappend` g v)
@@ -281,7 +268,6 @@ instance Bifoldable HashMap where
281
268
{-# INLINE bifoldr #-}
282
269
bifoldl f g = foldlWithKey (\ acc k v -> (acc `f` k) `g` v)
283
270
{-# INLINE bifoldl #-}
284
- #endif
285
271
286
272
-- | '<>' = 'union'
287
273
--
@@ -606,7 +592,6 @@ member k m = case lookup k m of
606
592
-- | /O(log n)/ Return the value to which the specified key is mapped,
607
593
-- or 'Nothing' if this map contains no mapping for the key.
608
594
lookup :: (Eq k , Hashable k ) => k -> HashMap k v -> Maybe v
609
- #if __GLASGOW_HASKELL__ >= 802
610
595
-- GHC does not yet perform a worker-wrapper transformation on
611
596
-- unboxed sums automatically. That seems likely to happen at some
612
597
-- 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 #)
619
604
lookup # k m = lookupCont (\ _ -> (# (# # ) | # )) (\ v _i -> (# | v # )) (hash k) k 0 m
620
605
{-# INLINABLE lookup# #-}
621
606
622
- #else
623
-
624
- lookup k m = lookupCont (\ _ -> Nothing ) (\ v _i -> Just v) (hash k) k 0 m
625
- {-# INLINABLE lookup #-}
626
- #endif
627
-
628
607
-- | lookup' is a version of lookup that takes the hash separately.
629
608
-- It is used to implement alterF.
630
609
lookup' :: Eq k => Hash -> k -> HashMap k v -> Maybe v
631
- #if __GLASGOW_HASKELL__ >= 802
632
610
-- GHC does not yet perform a worker-wrapper transformation on
633
611
-- unboxed sums automatically. That seems likely to happen at some
634
612
-- 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
639
617
(# (# # ) | # ) -> Nothing
640
618
(# | (# a, _i # ) # ) -> Just a
641
619
{-# INLINE lookup' #-}
642
- #else
643
- lookup' h k m = lookupCont (\ _ -> Nothing ) (\ v _i -> Just v) h k 0 m
644
- {-# INLINABLE lookup' #-}
645
- #endif
646
620
647
621
-- The result of a lookup, keeping track of if a hash collision occured.
648
622
-- 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
662
636
-- Key in map, no collision => Present v (-1)
663
637
-- Key in map, collision => Present v position
664
638
lookupRecordCollision :: Eq k => Hash -> k -> HashMap k v -> LookupRes v
665
- #if __GLASGOW_HASKELL__ >= 802
666
639
lookupRecordCollision h k m = case lookupRecordCollision# h k m of
667
640
(# (# # ) | # ) -> Absent
668
641
(# | (# a, i # ) # ) -> Present a (I # i) -- GHC will eliminate the I#
@@ -679,12 +652,6 @@ lookupRecordCollision# h k m =
679
652
-- INLINABLE to specialize to the Eq instance.
680
653
{-# INLINABLE lookupRecordCollision# #-}
681
654
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
-
688
655
-- A two-continuation version of lookupRecordCollision. This lets us
689
656
-- share source code between lookup and lookupRecordCollision without
690
657
-- risking any performance degradation.
@@ -698,11 +665,7 @@ lookupRecordCollision h k m = lookupCont (\_ -> Absent) Present h k 0 m
698
665
-- keys at the top-level of a hashmap, the offset should be 0. When looking up
699
666
-- keys at level @n@ of a hashmap, the offset should be @n * bitsPerSubkey@.
700
667
lookupCont ::
701
- #if __GLASGOW_HASKELL__ >= 802
702
668
forall rep (r :: TYPE rep ) k v .
703
- #else
704
- forall r k v.
705
- #endif
706
669
Eq k
707
670
=> ((# # ) -> r ) -- Absent continuation
708
671
-> (v -> Int -> r ) -- Present continuation
@@ -2155,11 +2118,7 @@ fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty
2155
2118
-- | /O(n)/ Look up the value associated with the given key in an
2156
2119
-- array.
2157
2120
lookupInArrayCont ::
2158
- #if __GLASGOW_HASKELL__ >= 802
2159
2121
forall rep (r :: TYPE rep ) k v .
2160
- #else
2161
- forall r k v.
2162
- #endif
2163
2122
Eq k => ((# # ) -> r ) -> (v -> Int -> r ) -> k -> A. Array (Leaf k v ) -> r
2164
2123
lookupInArrayCont absent present k0 ary0 = go k0 ary0 0 (A. length ary0)
2165
2124
where
0 commit comments