Skip to content

Commit 4af4999

Browse files
committed
Add nub
Resolves #560.
1 parent eb955f5 commit 4af4999

File tree

1 file changed

+49
-0
lines changed

1 file changed

+49
-0
lines changed

Data/HashMap/Internal.hs

Lines changed: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -148,6 +148,7 @@ module Data.HashMap.Internal
148148
, insertModifying
149149
, ptrEq
150150
, adjust#
151+
, nub
151152
) where
152153

153154
import Data.Traversable -- MicroHs needs this since its Prelude does not have Foldable&Traversable.
@@ -156,6 +157,7 @@ import Data.Traversable -- MicroHs needs this since its Prelude does n
156157
import Control.Applicative (Const (..))
157158
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
158159
import Control.Monad.ST (ST, runST)
160+
import Control.Monad.ST.Unsafe (unsafeInterleaveST)
159161
import Data.Bifoldable (Bifoldable (..))
160162
import Data.Bits (complement, countTrailingZeros, popCount,
161163
shiftL, unsafeShiftL, unsafeShiftR, (.&.),
@@ -994,6 +996,38 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
994996
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t)
995997
{-# INLINABLE unsafeInsert #-}
996998

999+
unsafeInsertNewKeyM :: Hash -> k -> v -> HashMap k v -> ST s (HashMap k v)
1000+
unsafeInsertNewKeyM = unsafeInsertNewKeyInSubtreeM 0
1001+
{-# INLINE unsafeInsertNewKeyM #-}
1002+
1003+
unsafeInsertNewKeyInSubtreeM :: Shift -> Hash -> k -> v -> HashMap k v -> ST s (HashMap k v)
1004+
unsafeInsertNewKeyInSubtreeM !s !h !k v = \case
1005+
Empty -> pure $! Leaf h (L k v)
1006+
t@(Leaf hy ly)
1007+
| h == hy -> pure $! collision h ly (L k v)
1008+
| otherwise -> two s h k v hy t
1009+
t@(BitmapIndexed bm ary)
1010+
| bm .&. m == 0 -> do
1011+
ary' <- A.insertM ary i $! Leaf h (L k v)
1012+
pure $! bitmapIndexedOrFull (bm .|. m) ary'
1013+
| otherwise -> do
1014+
st <- A.indexM ary i
1015+
st' <- unsafeInsertNewKeyInSubtreeM (nextShift s) h k v st
1016+
A.unsafeUpdateM ary i st'
1017+
pure t
1018+
where
1019+
m = mask h s
1020+
i = sparseIndex bm m
1021+
t@(Full ary) -> do
1022+
let !i = index h s
1023+
st <- A.indexM ary i
1024+
st' <- unsafeInsertNewKeyInSubtreeM (nextShift s) h k v st
1025+
A.unsafeUpdateM ary i st'
1026+
pure t
1027+
t@(Collision hy ary)
1028+
| h == hy -> pure $! Collision h (A.snoc ary $! L k v)
1029+
| otherwise -> two s h k v hy t
1030+
9971031
-- | Create a map from two key-value pairs which hashes don't collide. To
9981032
-- enhance sharing, the second key-value pair is represented by the hash of its
9991033
-- key and a singleton HashMap pairing its key with its value.
@@ -2898,3 +2932,18 @@ instance Hashable k => Exts.IsList (HashMap k v) where
28982932
fromList = fromList
28992933
toList = toList
29002934
#endif
2935+
2936+
nub :: Hashable a => [a] -> [a]
2937+
nub = \l -> runST (nub_ l empty)
2938+
where
2939+
nub_ [] _seen = pure []
2940+
nub_ (x:xs) seen
2941+
| Just _ <- lookup' h x seen = nub_ xs seen
2942+
| otherwise = do
2943+
rest <- unsafeInterleaveST $ do
2944+
seen' <- unsafeInsertNewKeyM h x () seen
2945+
nub_ xs seen'
2946+
pure (x : rest)
2947+
where
2948+
h = hash x
2949+
{-# INLINABLE nub #-}

0 commit comments

Comments
 (0)