@@ -194,7 +194,7 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
194
194
195
195
-- | @since 0.2.14.0
196
196
instance NFData k => NFData1 (Leaf k ) where
197
- liftRnf rnf2 = liftRnf2 rnf rnf2
197
+ liftRnf = liftRnf2 rnf
198
198
199
199
-- | @since 0.2.14.0
200
200
instance NFData2 Leaf where
@@ -226,7 +226,7 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
226
226
227
227
-- | @since 0.2.14.0
228
228
instance NFData k => NFData1 (HashMap k ) where
229
- liftRnf rnf2 = liftRnf2 rnf rnf2
229
+ liftRnf = liftRnf2 rnf
230
230
231
231
-- | @since 0.2.14.0
232
232
instance NFData2 HashMap where
@@ -334,8 +334,7 @@ instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
334
334
instance (Eq k , Hashable k , Read k , Read e ) => Read (HashMap k e ) where
335
335
readPrec = parens $ prec 10 $ do
336
336
Ident " fromList" <- lexP
337
- xs <- readPrec
338
- return (fromList xs)
337
+ fromList <$> readPrec
339
338
340
339
readListPrec = readListPrecDefault
341
340
@@ -717,7 +716,7 @@ findWithDefault def k t = case lookup k t of
717
716
lookupDefault :: (Eq k , Hashable k )
718
717
=> v -- ^ Default value to return.
719
718
-> k -> HashMap k v -> v
720
- lookupDefault def k t = findWithDefault def k t
719
+ lookupDefault = findWithDefault
721
720
{-# INLINE lookupDefault #-}
722
721
723
722
-- | /O(log n)/ Return the value to which the specified key is mapped.
@@ -968,7 +967,7 @@ insertModifying x f k0 m0 = go h0 k0 0 m0
968
967
| hy == h = if ky == k
969
968
then case f y of
970
969
(# v' # ) | ptrEq y v' -> t
971
- | otherwise -> Leaf h (L k (v') )
970
+ | otherwise -> Leaf h (L k v' )
972
971
else collision h l (L k x)
973
972
| otherwise = runST (two s h k x hy t)
974
973
go h k s t@ (BitmapIndexed b ary)
@@ -1264,10 +1263,9 @@ alterF f = \ !k !m ->
1264
1263
let
1265
1264
! h = hash k
1266
1265
mv = lookup' h k m
1267
- in (<$> f mv) $ \ fres ->
1268
- case fres of
1269
- Nothing -> maybe m (const (delete' h k m)) mv
1270
- Just v' -> insert' h k v' m
1266
+ in (<$> f mv) $ \ case
1267
+ Nothing -> maybe m (const (delete' h k m)) mv
1268
+ Just v' -> insert' h k v' m
1271
1269
1272
1270
-- We unconditionally rewrite alterF in RULES, but we expose an
1273
1271
-- unfolding just in case it's used in some way that prevents the
@@ -1356,8 +1354,7 @@ alterFWeird _ _ f = alterFEager f
1356
1354
-- eagerly, whether or not the given function requires that information.
1357
1355
alterFEager :: (Functor f , Eq k , Hashable k )
1358
1356
=> (Maybe v -> f (Maybe v )) -> k -> HashMap k v -> f (HashMap k v )
1359
- alterFEager f ! k m = (<$> f mv) $ \ fres ->
1360
- case fres of
1357
+ alterFEager f ! k m = (<$> f mv) $ \ case
1361
1358
1362
1359
------------------------------
1363
1360
-- Delete the key from the map.
@@ -1407,7 +1404,7 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
1407
1404
--
1408
1405
-- @since 0.2.12
1409
1406
isSubmapOf :: (Eq k , Hashable k , Eq v ) => HashMap k v -> HashMap k v -> Bool
1410
- isSubmapOf = ( Exts. inline isSubmapOfBy) (==)
1407
+ isSubmapOf = Exts. inline isSubmapOfBy (==)
1411
1408
{-# INLINABLE isSubmapOf #-}
1412
1409
1413
1410
-- | /O(n*log m)/ Inclusion of maps with value comparison. A map is included in
@@ -1634,10 +1631,10 @@ unionArrayBy f b1 b2 ary1 ary2 = A.run $ do
1634
1631
go (i+ 1 ) (i1+ 1 ) (i2+ 1 ) (m `unsafeShiftL` 1 )
1635
1632
| b1 .&. m /= 0 = do
1636
1633
A. write mary i =<< A. indexM ary1 i1
1637
- go (i+ 1 ) (i1+ 1 ) ( i2 ) (m `unsafeShiftL` 1 )
1634
+ go (i+ 1 ) (i1+ 1 ) i2 (m `unsafeShiftL` 1 )
1638
1635
| otherwise = do
1639
1636
A. write mary i =<< A. indexM ary2 i2
1640
- go (i+ 1 ) ( i1 ) (i2+ 1 ) (m `unsafeShiftL` 1 )
1637
+ go (i+ 1 ) i1 (i2+ 1 ) (m `unsafeShiftL` 1 )
1641
1638
go 0 0 0 (b' .&. negate b') -- XXX: b' must be non-zero
1642
1639
return mary
1643
1640
-- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
@@ -2268,7 +2265,7 @@ mask w s = 1 `unsafeShiftL` index w s
2268
2265
-- | Mask out the 'bitsPerSubkey' bits used for indexing at this level
2269
2266
-- of the tree.
2270
2267
index :: Hash -> Shift -> Int
2271
- index w s = fromIntegral $ ( unsafeShiftR w s) .&. subkeyMask
2268
+ index w s = fromIntegral $ unsafeShiftR w s .&. subkeyMask
2272
2269
{-# INLINE index #-}
2273
2270
2274
2271
-- | A bitmask with the 'bitsPerSubkey' least significant bits set.
0 commit comments