Skip to content

Commit afd8d9b

Browse files
authored
Use Shift type synonym where appropriate (#556)
d06eb34 had introduced some type signatures using `Int` where `Shift` would be more specific.
1 parent 9c19d1e commit afd8d9b

File tree

2 files changed

+12
-12
lines changed

2 files changed

+12
-12
lines changed

Data/HashMap/Internal.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -963,7 +963,7 @@ unsafeInsert :: forall k v. (Eq k, Hashable k) => k -> v -> HashMap k v -> HashM
963963
unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
964964
where
965965
h0 = hash k0
966-
go :: forall s. Hash -> k -> v -> Int -> HashMap k v -> ST s (HashMap k v)
966+
go :: forall s. Hash -> k -> v -> Shift -> HashMap k v -> ST s (HashMap k v)
967967
go !h !k x !_ Empty = return $! Leaf h (L k x)
968968
go h k x s t@(Leaf hy l@(L ky y))
969969
| hy == h = if ky == k

Data/HashMap/Internal/Strict.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,11 @@
1-
{-# LANGUAGE BangPatterns #-}
2-
{-# LANGUAGE CPP #-}
3-
{-# LANGUAGE LambdaCase #-}
4-
{-# LANGUAGE MagicHash #-}
5-
{-# LANGUAGE PatternGuards #-}
1+
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE LambdaCase #-}
4+
{-# LANGUAGE MagicHash #-}
5+
{-# LANGUAGE PatternGuards #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
7-
{-# LANGUAGE Trustworthy #-}
8-
{-# LANGUAGE UnboxedTuples #-}
7+
{-# LANGUAGE Trustworthy #-}
8+
{-# LANGUAGE UnboxedTuples #-}
99
{-# OPTIONS_HADDOCK not-home #-}
1010

1111
------------------------------------------------------------------------
@@ -126,15 +126,15 @@ module Data.HashMap.Internal.Strict
126126
) where
127127

128128
import Control.Applicative (Const (..))
129-
import Control.Monad.ST (runST, ST)
129+
import Control.Monad.ST (ST, runST)
130130
import Data.Bits ((.&.), (.|.))
131131
import Data.Coerce (coerce)
132132
import Data.Functor.Identity (Identity (..))
133133
-- See Note [Imports from Data.HashMap.Internal]
134134
import Data.Hashable (Hashable)
135135
import Data.HashMap.Internal (Hash, HashMap (..), Leaf (..), LookupRes (..),
136-
fullBitmap, hash, index, mask, nextShift, ptrEq,
137-
sparseIndex)
136+
Shift, fullBitmap, hash, index, mask, nextShift,
137+
ptrEq, sparseIndex)
138138
import Prelude hiding (lookup, map)
139139

140140
-- See Note [Imports from Data.HashMap.Internal]
@@ -235,7 +235,7 @@ unsafeInsertWithKey :: forall k v. (Eq k, Hashable k) => (k -> v -> v -> v) -> k
235235
unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
236236
where
237237
h0 = hash k0
238-
go :: forall s. Hash -> k -> v -> Int -> HashMap k v -> ST s (HashMap k v)
238+
go :: forall s. Hash -> k -> v -> Shift -> HashMap k v -> ST s (HashMap k v)
239239
go !h !k x !_ Empty = return $! leaf h k x
240240
go h k x s t@(Leaf hy l@(L ky y))
241241
| hy == h = if ky == k

0 commit comments

Comments
 (0)