Skip to content

Commit ef84b0b

Browse files
committed
Make setting of hash optional in fromList
1 parent 1162033 commit ef84b0b

File tree

3 files changed

+57
-19
lines changed

3 files changed

+57
-19
lines changed

Data/HashMap/Internal.hs

Lines changed: 28 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -103,6 +103,7 @@ module Data.HashMap.Internal
103103
-- ** Lists
104104
, toList
105105
, fromList
106+
, fromList'
106107
, fromListWith
107108
, fromListWithKey
108109

@@ -337,10 +338,10 @@ instance (Eq k, Hashable k, KnownNat salt) => Monoid (HashMapT salt k v) where
337338
{-# INLINE mappend #-}
338339

339340
instance (Data k, Data v, Eq k, Hashable k, KnownNat salt) => Data (HashMapT salt k v) where
340-
gfoldl f z m = z fromList `f` toList m
341+
gfoldl f z m = z fromList' `f` toList m
341342
toConstr _ = fromListConstr
342343
gunfold k z c = case constrIndex c of
343-
1 -> k (z fromList)
344+
1 -> k (z fromList')
344345
_ -> error "gunfold"
345346
dataTypeOf _ = hashMapDataType
346347
dataCast2 f = gcast2 f
@@ -368,7 +369,7 @@ instance Show k => Show1 (HashMapT salt k) where
368369

369370
instance (Eq k, Hashable k, Read k, KnownNat salt) => Read1 (HashMapT salt k) where
370371
liftReadsPrec rp rl = readsData $
371-
readsUnaryWith (liftReadsPrec rp' rl') "fromList" fromList
372+
readsUnaryWith (liftReadsPrec rp' rl') "fromList" fromList'
372373
where
373374
rp' = liftReadsPrec rp rl
374375
rl' = liftReadList rp rl
@@ -378,7 +379,7 @@ instance (Eq k, Hashable k, Read k, Read e, KnownNat salt) => Read (HashMapT sal
378379
readPrec = parens $ prec 10 $ do
379380
Ident "fromList" <- lexP
380381
xs <- readPrec
381-
return (fromList xs)
382+
return (fromList' xs)
382383

383384
readListPrec = readListPrecDefault
384385

@@ -1826,7 +1827,7 @@ traverseWithKey f = go
18261827
--
18271828
-- @since 0.2.14.0
18281829
mapKeys :: (Eq k2, Hashable k2, KnownNat salt) => (k1 -> k2) -> HashMapT salt k1 v -> HashMapT salt k2 v
1829-
mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
1830+
mapKeys f = fromList' . foldrWithKey (\k x xs -> (f k, x) : xs) []
18301831

18311832
------------------------------------------------------------------------
18321833
-- * Difference and intersection
@@ -2126,10 +2127,15 @@ toList t = build (\ c z -> foldrWithKey (curry c) z t)
21262127

21272128
-- | /O(n)/ Construct a map with the supplied mappings. If the list
21282129
-- contains duplicate mappings, the later mappings take precedence.
2129-
fromList :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
2130-
fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty'
2130+
fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
2131+
fromList = fromList'
21312132
{-# INLINABLE fromList #-}
21322133

2134+
-- | Same as 'fromList' but allows setting of a custom salt.
2135+
fromList' :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
2136+
fromList' = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty'
2137+
{-# INLINABLE fromList' #-}
2138+
21332139
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
21342140
-- the provided function @f@ to merge duplicate entries with
21352141
-- @(f newVal oldVal)@.
@@ -2160,10 +2166,15 @@ fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty'
21602166
--
21612167
-- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
21622168
-- > = fromList [(k, f d (f c (f b a)))]
2163-
fromListWith :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2164-
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
2169+
fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v
2170+
fromListWith = fromListWith'
21652171
{-# INLINE fromListWith #-}
21662172

2173+
-- | same as 'fromListWith' but allows setting of custom salt
2174+
fromListWith' :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2175+
fromListWith' f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
2176+
{-# INLINE fromListWith' #-}
2177+
21672178
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
21682179
-- the provided function to merge duplicate entries.
21692180
--
@@ -2190,10 +2201,15 @@ fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
21902201
-- > = fromList [(k, f k d (f k c (f k b a)))]
21912202
--
21922203
-- @since 0.2.11
2193-
fromListWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2194-
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
2204+
fromListWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v
2205+
fromListWithKey = fromListWithKey'
21952206
{-# INLINE fromListWithKey #-}
21962207

2208+
-- | same as 'fromListWithKey' but allows setting of custom salt
2209+
fromListWithKey' :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2210+
fromListWithKey' f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
2211+
{-# INLINE fromListWithKey' #-}
2212+
21972213
------------------------------------------------------------------------
21982214
-- Array operations
21992215

@@ -2378,5 +2394,5 @@ ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y ==# 1#)
23782394
-- IsList instance
23792395
instance (Eq k, Hashable k, KnownNat salt) => Exts.IsList (HashMapT salt k v) where
23802396
type Item (HashMapT salt k v) = (k, v)
2381-
fromList = fromList
2397+
fromList = fromList'
23822398
toList = toList

Data/HashMap/Internal/Strict.hs

Lines changed: 26 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -118,6 +118,9 @@ module Data.HashMap.Internal.Strict
118118
, fromList
119119
, fromListWith
120120
, fromListWithKey
121+
, fromList'
122+
, fromListWith'
123+
, fromListWithKey'
121124
) where
122125

123126
import Data.Bits ((.&.), (.|.))
@@ -136,7 +139,9 @@ import Data.HashMap.Internal hiding (
136139
insert, insertWith, singleton',
137140
differenceWith, intersectionWith, intersectionWithKey, map, mapWithKey,
138141
mapMaybe, mapMaybeWithKey, singleton, update, unionWith, unionWithKey,
139-
traverseWithKey)
142+
traverseWithKey
143+
, fromListWithKey', fromListWith', fromList'
144+
)
140145
import Data.HashMap.Internal.Unsafe (runST)
141146
#if MIN_VERSION_base(4,8,0)
142147
import Data.Functor.Identity
@@ -642,10 +647,15 @@ intersectionWithKey f a b = foldlWithKey' go empty' a
642647
-- | /O(n*log n)/ Construct a map with the supplied mappings. If the
643648
-- list contains duplicate mappings, the later mappings take
644649
-- precedence.
645-
fromList :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
646-
fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty'
650+
fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
651+
fromList = fromList'
647652
{-# INLINABLE fromList #-}
648653

654+
-- | Same as 'fromList' but allows setting of a custom salt.
655+
fromList' :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
656+
fromList' = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty'
657+
{-# INLINABLE fromList' #-}
658+
649659
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
650660
-- the provided function @f@ to merge duplicate entries with
651661
-- @(f newVal oldVal)@.
@@ -676,10 +686,15 @@ fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty'
676686
--
677687
-- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
678688
-- > = fromList [(k, f d (f c (f b a)))]
679-
fromListWith :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
680-
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
689+
fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v
690+
fromListWith = fromListWith'
681691
{-# INLINE fromListWith #-}
682692

693+
-- | same as 'fromListWith' but allows setting of custom salt
694+
fromListWith' :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
695+
fromListWith' f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
696+
{-# INLINE fromListWith' #-}
697+
683698
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
684699
-- the provided function to merge duplicate entries.
685700
--
@@ -706,10 +721,14 @@ fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
706721
-- > = fromList [(k, f k d (f k c (f k b a)))]
707722
--
708723
-- @since 0.2.11
709-
fromListWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
710-
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
724+
fromListWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> [(k, v)] -> HashMap k v
725+
fromListWithKey = fromListWithKey'
711726
{-# INLINE fromListWithKey #-}
712727

728+
-- | same as 'fromListWithKey' but allows setting of custom salt
729+
fromListWithKey' :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
730+
fromListWithKey' f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
731+
{-# INLINE fromListWithKey' #-}
713732
------------------------------------------------------------------------
714733
-- Array operations
715734

Data/HashMap/Strict.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -101,6 +101,9 @@ module Data.HashMap.Strict
101101
, fromList
102102
, fromListWith
103103
, fromListWithKey
104+
, fromList'
105+
, fromListWith'
106+
, fromListWithKey'
104107

105108
-- ** HashSets
106109
, HS.keysSet

0 commit comments

Comments
 (0)