|
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 #-} |
6 | 6 | {-# LANGUAGE ScopedTypeVariables #-} |
7 | | -{-# LANGUAGE Trustworthy #-} |
8 | | -{-# LANGUAGE UnboxedTuples #-} |
| 7 | +{-# LANGUAGE Trustworthy #-} |
| 8 | +{-# LANGUAGE UnboxedTuples #-} |
9 | 9 | {-# OPTIONS_HADDOCK not-home #-} |
10 | 10 |
|
11 | 11 | ------------------------------------------------------------------------ |
@@ -126,15 +126,15 @@ module Data.HashMap.Internal.Strict |
126 | 126 | ) where |
127 | 127 |
|
128 | 128 | import Control.Applicative (Const (..)) |
129 | | -import Control.Monad.ST (runST, ST) |
| 129 | +import Control.Monad.ST (ST, runST) |
130 | 130 | import Data.Bits ((.&.), (.|.)) |
131 | 131 | import Data.Coerce (coerce) |
132 | 132 | import Data.Functor.Identity (Identity (..)) |
133 | 133 | -- See Note [Imports from Data.HashMap.Internal] |
134 | 134 | import Data.Hashable (Hashable) |
135 | 135 | 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) |
138 | 138 | import Prelude hiding (lookup, map) |
139 | 139 |
|
140 | 140 | -- See Note [Imports from Data.HashMap.Internal] |
@@ -235,7 +235,7 @@ unsafeInsertWithKey :: forall k v. (Eq k, Hashable k) => (k -> v -> v -> v) -> k |
235 | 235 | unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0) |
236 | 236 | where |
237 | 237 | 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) |
239 | 239 | go !h !k x !_ Empty = return $! leaf h k x |
240 | 240 | go h k x s t@(Leaf hy l@(L ky y)) |
241 | 241 | | hy == h = if ky == k |
|
0 commit comments