Skip to content

Address some hlint warnings #371

New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

Merged
merged 2 commits into from
Mar 11, 2022
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
29 changes: 13 additions & 16 deletions Data/HashMap/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -194,7 +194,7 @@ instance (TH.Lift k, TH.Lift v) => TH.Lift (Leaf k v) where

-- | @since 0.2.14.0
instance NFData k => NFData1 (Leaf k) where
liftRnf rnf2 = liftRnf2 rnf rnf2
liftRnf = liftRnf2 rnf

-- | @since 0.2.14.0
instance NFData2 Leaf where
Expand Down Expand Up @@ -226,7 +226,7 @@ instance (NFData k, NFData v) => NFData (HashMap k v) where

-- | @since 0.2.14.0
instance NFData k => NFData1 (HashMap k) where
liftRnf rnf2 = liftRnf2 rnf rnf2
liftRnf = liftRnf2 rnf

-- | @since 0.2.14.0
instance NFData2 HashMap where
Expand Down Expand Up @@ -334,8 +334,7 @@ instance (Eq k, Hashable k, Read k) => Read1 (HashMap k) where
instance (Eq k, Hashable k, Read k, Read e) => Read (HashMap k e) where
readPrec = parens $ prec 10 $ do
Ident "fromList" <- lexP
xs <- readPrec
return (fromList xs)
fromList <$> readPrec

readListPrec = readListPrecDefault

Expand Down Expand Up @@ -717,7 +716,7 @@ findWithDefault def k t = case lookup k t of
lookupDefault :: (Eq k, Hashable k)
=> v -- ^ Default value to return.
-> k -> HashMap k v -> v
lookupDefault def k t = findWithDefault def k t
lookupDefault = findWithDefault
{-# INLINE lookupDefault #-}

-- | /O(log n)/ Return the value to which the specified key is mapped.
Expand Down Expand Up @@ -968,7 +967,7 @@ insertModifying x f k0 m0 = go h0 k0 0 m0
| hy == h = if ky == k
then case f y of
(# v' #) | ptrEq y v' -> t
| otherwise -> Leaf h (L k (v'))
| otherwise -> Leaf h (L k v')
else collision h l (L k x)
| otherwise = runST (two s h k x hy t)
go h k s t@(BitmapIndexed b ary)
Expand Down Expand Up @@ -1264,10 +1263,9 @@ alterF f = \ !k !m ->
let
!h = hash k
mv = lookup' h k m
in (<$> f mv) $ \fres ->
case fres of
Nothing -> maybe m (const (delete' h k m)) mv
Just v' -> insert' h k v' m
in (<$> f mv) $ \case
Nothing -> maybe m (const (delete' h k m)) mv
Just v' -> insert' h k v' m

-- We unconditionally rewrite alterF in RULES, but we expose an
-- unfolding just in case it's used in some way that prevents the
Expand Down Expand Up @@ -1356,8 +1354,7 @@ alterFWeird _ _ f = alterFEager f
-- eagerly, whether or not the given function requires that information.
alterFEager :: (Functor f, Eq k, Hashable k)
=> (Maybe v -> f (Maybe v)) -> k -> HashMap k v -> f (HashMap k v)
alterFEager f !k m = (<$> f mv) $ \fres ->
case fres of
alterFEager f !k m = (<$> f mv) $ \case

------------------------------
-- Delete the key from the map.
Expand Down Expand Up @@ -1407,7 +1404,7 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
--
-- @since 0.2.12
isSubmapOf :: (Eq k, Hashable k, Eq v) => HashMap k v -> HashMap k v -> Bool
isSubmapOf = (Exts.inline isSubmapOfBy) (==)
isSubmapOf = Exts.inline isSubmapOfBy (==)
{-# INLINABLE isSubmapOf #-}

-- | /O(n*log m)/ Inclusion of maps with value comparison. A map is included in
Expand Down Expand Up @@ -1634,10 +1631,10 @@ unionArrayBy f b1 b2 ary1 ary2 = A.run $ do
go (i+1) (i1+1) (i2+1) (m `unsafeShiftL` 1)
| b1 .&. m /= 0 = do
A.write mary i =<< A.indexM ary1 i1
go (i+1) (i1+1) (i2 ) (m `unsafeShiftL` 1)
go (i+1) (i1+1) i2 (m `unsafeShiftL` 1)
| otherwise = do
A.write mary i =<< A.indexM ary2 i2
go (i+1) (i1 ) (i2+1) (m `unsafeShiftL` 1)
go (i+1) i1 (i2+1) (m `unsafeShiftL` 1)
go 0 0 0 (b' .&. negate b') -- XXX: b' must be non-zero
return mary
-- TODO: For the case where b1 .&. b2 == b1, i.e. when one is a
Expand Down Expand Up @@ -2268,7 +2265,7 @@ mask w s = 1 `unsafeShiftL` index w s
-- | Mask out the 'bitsPerSubkey' bits used for indexing at this level
-- of the tree.
index :: Hash -> Shift -> Int
index w s = fromIntegral $ (unsafeShiftR w s) .&. subkeyMask
index w s = fromIntegral $ unsafeShiftR w s .&. subkeyMask
{-# INLINE index #-}

-- | A bitmask with the 'bitsPerSubkey' least significant bits set.
Expand Down
14 changes: 7 additions & 7 deletions Data/HashMap/Internal/Strict.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE Trustworthy #-}
Expand Down Expand Up @@ -181,7 +182,7 @@ insertWith f k0 v0 m0 = go h0 k0 v0 0 m0
go h k x s t@(Leaf hy l@(L ky y))
| hy == h = if ky == k
then leaf h k (f x y)
else x `seq` (collision h l (L k x))
else x `seq` collision h l (L k x)
| otherwise = x `seq` runST (two s h k x hy t)
go h k x s (BitmapIndexed b ary)
| b .&. m == 0 =
Expand Down Expand Up @@ -221,7 +222,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
| hy == h = if ky == k
then return $! leaf h k (f k x y)
else do
let l' = x `seq` (L k x)
let l' = x `seq` L k x
return $! collision h l l'
| otherwise = x `seq` two s h k x hy t
go h k x s t@(BitmapIndexed b ary)
Expand Down Expand Up @@ -316,10 +317,9 @@ alterF :: (Functor f, Eq k, Hashable k)
alterF f = \ !k !m ->
let !h = hash k
mv = lookup' h k m
in (<$> f mv) $ \fres ->
case fres of
Nothing -> maybe m (const (delete' h k m)) mv
Just !v' -> insert' h k v' m
in (<$> f mv) $ \case
Nothing -> maybe m (const (delete' h k m)) mv
Just !v' -> insert' h k v' m

-- We rewrite this function unconditionally in RULES, but we expose
-- an unfolding just in case it's used in a context where the rules
Expand Down Expand Up @@ -734,7 +734,7 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
-- Not found, append to the end.
mary <- A.new_ (n + 1)
A.copy ary 0 mary 0 n
let !l = v `seq` (L k v)
let !l = v `seq` L k v
A.write mary n l
return mary
| otherwise = case A.index ary i of
Expand Down
5 changes: 2 additions & 3 deletions Data/HashSet/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -214,8 +214,7 @@ instance (Hashable a, Eq a) => Monoid (HashSet a) where
instance (Eq a, Hashable a, Read a) => Read (HashSet a) where
readPrec = parens $ prec 10 $ do
Ident "fromList" <- lexP
xs <- readPrec
return (fromList xs)
fromList <$> readPrec

readListPrec = readListPrecDefault

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

-- | /O(n*min(W, n))/ Construct a set from a list of elements.
Expand Down
2 changes: 1 addition & 1 deletion tests/Strictness.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ pSingletonKeyStrict :: Int -> Bool
pSingletonKeyStrict v = isBottom $ HM.singleton (bottom :: Key) v

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

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