Skip to content

Commit 7237826

Browse files
authored
Address some hlint warnings (#371)
1 parent f795586 commit 7237826

File tree

4 files changed

+23
-27
lines changed

4 files changed

+23
-27
lines changed

Data/HashMap/Internal.hs

Lines changed: 13 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -194,7 +194,7 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where
194194

195195
-- | @since 0.2.14.0
196196
instance NFData k => NFData1 (Leaf k) where
197-
liftRnf rnf2 = liftRnf2 rnf rnf2
197+
liftRnf = liftRnf2 rnf
198198

199199
-- | @since 0.2.14.0
200200
instance NFData2 Leaf where
@@ -226,7 +226,7 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where
226226

227227
-- | @since 0.2.14.0
228228
instance NFData k => NFData1 (HashMap k) where
229-
liftRnf rnf2 = liftRnf2 rnf rnf2
229+
liftRnf = liftRnf2 rnf
230230

231231
-- | @since 0.2.14.0
232232
instance NFData2 HashMap where
@@ -334,8 +334,7 @@ instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
334334
instance (Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) where
335335
readPrec = parens $ prec 10 $ do
336336
Ident "fromList" <- lexP
337-
xs <- readPrec
338-
return (fromList xs)
337+
fromList <$> readPrec
339338

340339
readListPrec = readListPrecDefault
341340

@@ -717,7 +716,7 @@ findWithDefault def k t = case lookup k t of
717716
lookupDefault :: (Eq k, Hashable k)
718717
=> v -- ^ Default value to return.
719718
-> k -> HashMap k v -> v
720-
lookupDefault def k t = findWithDefault def k t
719+
lookupDefault = findWithDefault
721720
{-# INLINE lookupDefault #-}
722721

723722
-- | /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
968967
| hy == h = if ky == k
969968
then case f y of
970969
(# v' #) | ptrEq y v' -> t
971-
| otherwise -> Leaf h (L k (v'))
970+
| otherwise -> Leaf h (L k v')
972971
else collision h l (L k x)
973972
| otherwise = runST (two s h k x hy t)
974973
go h k s t@(BitmapIndexed b ary)
@@ -1264,10 +1263,9 @@ alterF f = \ !k !m ->
12641263
let
12651264
!h = hash k
12661265
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
12711269

12721270
-- We unconditionally rewrite alterF in RULES, but we expose an
12731271
-- unfolding just in case it's used in some way that prevents the
@@ -1356,8 +1354,7 @@ alterFWeird _ _ f = alterFEager f
13561354
-- eagerly, whether or not the given function requires that information.
13571355
alterFEager :: (Functor f, Eq k, Hashable k)
13581356
=> (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
13611358

13621359
------------------------------
13631360
-- Delete the key from the map.
@@ -1407,7 +1404,7 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
14071404
--
14081405
-- @since 0.2.12
14091406
isSubmapOf :: (Eq k, Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool
1410-
isSubmapOf = (Exts.inline isSubmapOfBy) (==)
1407+
isSubmapOf = Exts.inline isSubmapOfBy (==)
14111408
{-# INLINABLE isSubmapOf #-}
14121409

14131410
-- | /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
16341631
go (i+1) (i1+1) (i2+1) (m `unsafeShiftL` 1)
16351632
| b1 .&. m /= 0 = do
16361633
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)
16381635
| otherwise = do
16391636
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)
16411638
go 0 0 0 (b' .&. negate b') -- XXX: b' must be non-zero
16421639
return mary
16431640
-- 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
22682265
-- | Mask out the 'bitsPerSubkey' bits used for indexing at this level
22692266
-- of the tree.
22702267
index :: Hash -> Shift -> Int
2271-
index w s = fromIntegral $ (unsafeShiftR w s) .&. subkeyMask
2268+
index w s = fromIntegral $ unsafeShiftR w s .&. subkeyMask
22722269
{-# INLINE index #-}
22732270

22742271
-- | A bitmask with the 'bitsPerSubkey' least significant bits set.

Data/HashMap/Internal/Strict.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE BangPatterns #-}
22
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE LambdaCase #-}
34
{-# LANGUAGE MagicHash #-}
45
{-# LANGUAGE PatternGuards #-}
56
{-# LANGUAGE Trustworthy #-}
@@ -181,7 +182,7 @@ insertWith f k0 v0 m0 = go h0 k0 v0 0 m0
181182
go h k x s t@(Leaf hy l@(L ky y))
182183
| hy == h = if ky == k
183184
then leaf h k (f x y)
184-
else x `seq` (collision h l (L k x))
185+
else x `seq` collision h l (L k x)
185186
| otherwise = x `seq` runST (two s h k x hy t)
186187
go h k x s (BitmapIndexed b ary)
187188
| b .&. m == 0 =
@@ -221,7 +222,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
221222
| hy == h = if ky == k
222223
then return $! leaf h k (f k x y)
223224
else do
224-
let l' = x `seq` (L k x)
225+
let l' = x `seq` L k x
225226
return $! collision h l l'
226227
| otherwise = x `seq` two s h k x hy t
227228
go h k x s t@(BitmapIndexed b ary)
@@ -316,10 +317,9 @@ alterF :: (Functor f, Eq k, Hashable k)
316317
alterF f = \ !k !m ->
317318
let !h = hash k
318319
mv = lookup' h k m
319-
in (<$> f mv) $ \fres ->
320-
case fres of
321-
Nothing -> maybe m (const (delete' h k m)) mv
322-
Just !v' -> insert' h k v' m
320+
in (<$> f mv) $ \case
321+
Nothing -> maybe m (const (delete' h k m)) mv
322+
Just !v' -> insert' h k v' m
323323

324324
-- We rewrite this function unconditionally in RULES, but we expose
325325
-- an unfolding just in case it's used in a context where the rules
@@ -734,7 +734,7 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
734734
-- Not found, append to the end.
735735
mary <- A.new_ (n + 1)
736736
A.copy ary 0 mary 0 n
737-
let !l = v `seq` (L k v)
737+
let !l = v `seq` L k v
738738
A.write mary n l
739739
return mary
740740
| otherwise = case A.index ary i of

Data/HashSet/Internal.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -214,8 +214,7 @@ instance (Hashable a, Eq a) => Monoid (HashSet a) where
214214
instance (Eq a, Hashable a, Read a) => Read (HashSet a) where
215215
readPrec = parens $ prec 10 $ do
216216
Ident "fromList" <- lexP
217-
xs <- readPrec
218-
return (fromList xs)
217+
fromList <$> readPrec
219218

220219
readListPrec = readListPrecDefault
221220

@@ -442,7 +441,7 @@ filter p = HashSet . H.filterWithKey q . asMap
442441
-- | /O(n)/ Return a list of this set's elements. The list is
443442
-- produced lazily.
444443
toList :: HashSet a -> [a]
445-
toList t = Exts.build (\ c z -> foldrWithKey ((const .) c) z (asMap t))
444+
toList t = Exts.build (\ c z -> foldrWithKey (const . c) z (asMap t))
446445
{-# INLINE toList #-}
447446

448447
-- | /O(n*min(W, n))/ Construct a set from a list of elements.

tests/Strictness.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ pSingletonKeyStrict :: Int -> Bool
4848
pSingletonKeyStrict v = isBottom $ HM.singleton (bottom :: Key) v
4949

5050
pSingletonValueStrict :: Key -> Bool
51-
pSingletonValueStrict k = isBottom $ (HM.singleton k (bottom :: Int))
51+
pSingletonValueStrict k = isBottom $ HM.singleton k (bottom :: Int)
5252

5353
pLookupDefaultKeyStrict :: Int -> HashMap Key Int -> Bool
5454
pLookupDefaultKeyStrict def m = isBottom $ HM.lookupDefault def bottom m

0 commit comments

Comments
 (0)