Skip to content

Commit c1220e8

Browse files
committed
Adress deprecation warnings
Fixes #505
1 parent db40495 commit c1220e8

File tree

2 files changed

+18
-14
lines changed

2 files changed

+18
-14
lines changed

Data/HashMap/Internal.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,12 +4,12 @@
44
{-# LANGUAGE LambdaCase #-}
55
{-# LANGUAGE MagicHash #-}
66
{-# LANGUAGE PatternGuards #-}
7+
{-# LANGUAGE PolyKinds #-}
78
{-# LANGUAGE RoleAnnotations #-}
89
{-# LANGUAGE ScopedTypeVariables #-}
910
{-# LANGUAGE StandaloneDeriving #-}
1011
{-# LANGUAGE TemplateHaskellQuotes #-}
1112
{-# LANGUAGE TypeFamilies #-}
12-
{-# LANGUAGE TypeInType #-}
1313
{-# LANGUAGE UnboxedSums #-}
1414
{-# LANGUAGE UnboxedTuples #-}
1515
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
@@ -166,7 +166,7 @@ import Data.HashMap.Internal.List (isPermutationBy, unorderedCompare)
166166
import Data.Semigroup (Semigroup (..), stimesIdempotentMonoid)
167167
import GHC.Exts (Int (..), Int#, TYPE, (==#))
168168
import GHC.Stack (HasCallStack)
169-
import Prelude hiding (Foldable(..), filter, lookup, map,
169+
import Prelude hiding (Foldable (..), filter, lookup, map,
170170
pred)
171171
import Text.Read hiding (step)
172172

@@ -1948,13 +1948,14 @@ intersectionArrayBy f !b1 !b2 !ary1 !ary2
19481948
intersectionCollisions :: Eq k => (k -> v1 -> v2 -> (# v3 #)) -> Hash -> Hash -> A.Array (Leaf k v1) -> A.Array (Leaf k v2) -> HashMap k v3
19491949
intersectionCollisions f h1 h2 ary1 ary2
19501950
| h1 == h2 = runST $ do
1951-
mary2 <- A.thaw ary2 0 $ A.length ary2
1952-
mary <- A.new_ $ min (A.length ary1) (A.length ary2)
1951+
let n2 = A.length ary2
1952+
mary2 <- A.thaw ary2 0 n2
1953+
mary <- A.new_ $ min (A.length ary1) n2
19531954
let go i j
1954-
| i >= A.length ary1 || j >= A.lengthM mary2 = pure j
1955+
| i >= A.length ary1 || j >= n2 = pure j
19551956
| otherwise = do
19561957
L k1 v1 <- A.indexM ary1 i
1957-
searchSwap k1 j mary2 >>= \case
1958+
searchSwap mary2 n2 k1 j >>= \case
19581959
Just (L _k2 v2) -> do
19591960
let !(# v3 #) = f k1 v1 v2
19601961
A.write mary j $ L k1 v3
@@ -1978,18 +1979,18 @@ intersectionCollisions f h1 h2 ary1 ary2
19781979
-- undefined 2 1 4
19791980
-- @
19801981
-- We don't actually need to write undefined, we just have to make sure that the next search starts 1 after the current one.
1981-
searchSwap :: Eq k => k -> Int -> A.MArray s (Leaf k v) -> ST s (Maybe (Leaf k v))
1982-
searchSwap toFind start = go start toFind start
1982+
searchSwap :: Eq k => A.MArray s (Leaf k v) -> Int -> k -> Int -> ST s (Maybe (Leaf k v))
1983+
searchSwap mary n toFind start = go start toFind start
19831984
where
1984-
go i0 k i mary
1985-
| i >= A.lengthM mary = pure Nothing
1985+
go i0 k i
1986+
| i >= n = pure Nothing
19861987
| otherwise = do
19871988
l@(L k' _v) <- A.read mary i
19881989
if k == k'
19891990
then do
19901991
A.write mary i =<< A.read mary i0
19911992
pure $ Just l
1992-
else go i0 k (i + 1) mary
1993+
else go i0 k (i + 1)
19931994
{-# INLINE searchSwap #-}
19941995

19951996
------------------------------------------------------------------------

Data/HashMap/Internal/Array.hs

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ import GHC.Exts (Int (..), SmallArray#, SmallMutableArray#,
8989
copySmallMutableArray#, indexSmallArray#,
9090
newSmallArray#, readSmallArray#,
9191
reallyUnsafePtrEquality#, sizeofSmallArray#,
92-
sizeofSmallMutableArray#, tagToEnum#,
92+
getSizeofSmallMutableArray#, tagToEnum#,
9393
thawSmallArray#, unsafeCoerce#,
9494
unsafeFreezeSmallArray#, unsafeThawSmallArray#,
9595
writeSmallArray#)
@@ -158,8 +158,11 @@ data MArray s a = MArray {
158158
unMArray :: !(SmallMutableArray# s a)
159159
}
160160

161-
lengthM :: MArray s a -> Int
162-
lengthM mary = I# (sizeofSmallMutableArray# (unMArray mary))
161+
lengthM :: MArray s a -> ST s Int
162+
lengthM (MArray ary) =
163+
ST $ \s ->
164+
case getSizeofSmallMutableArray# ary s of
165+
(# s', n #) -> (# s', I# n #)
163166
{-# INLINE lengthM #-}
164167

165168
------------------------------------------------------------------------

0 commit comments

Comments
 (0)