@@ -103,6 +103,7 @@ module Data.HashMap.Internal
103
103
-- ** Lists
104
104
, toList
105
105
, fromList
106
+ , fromList'
106
107
, fromListWith
107
108
, fromListWithKey
108
109
@@ -337,10 +338,10 @@ instance (Eq k, Hashable k, KnownNat salt) => Monoid (HashMapT salt k v) where
337
338
{-# INLINE mappend #-}
338
339
339
340
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
341
342
toConstr _ = fromListConstr
342
343
gunfold k z c = case constrIndex c of
343
- 1 -> k (z fromList)
344
+ 1 -> k (z fromList' )
344
345
_ -> error " gunfold"
345
346
dataTypeOf _ = hashMapDataType
346
347
dataCast2 f = gcast2 f
@@ -368,7 +369,7 @@ instance Show k => Show1 (HashMapT salt k) where
368
369
369
370
instance (Eq k , Hashable k , Read k , KnownNat salt ) => Read1 (HashMapT salt k ) where
370
371
liftReadsPrec rp rl = readsData $
371
- readsUnaryWith (liftReadsPrec rp' rl') " fromList" fromList
372
+ readsUnaryWith (liftReadsPrec rp' rl') " fromList" fromList'
372
373
where
373
374
rp' = liftReadsPrec rp rl
374
375
rl' = liftReadList rp rl
@@ -378,7 +379,7 @@ instance (Eq k, Hashable k, Read k, Read e, KnownNat salt) => Read (HashMapT sal
378
379
readPrec = parens $ prec 10 $ do
379
380
Ident " fromList" <- lexP
380
381
xs <- readPrec
381
- return (fromList xs)
382
+ return (fromList' xs)
382
383
383
384
readListPrec = readListPrecDefault
384
385
@@ -1826,7 +1827,7 @@ traverseWithKey f = go
1826
1827
--
1827
1828
-- @since 0.2.14.0
1828
1829
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) []
1830
1831
1831
1832
------------------------------------------------------------------------
1832
1833
-- * Difference and intersection
@@ -2126,10 +2127,15 @@ toList t = build (\ c z -> foldrWithKey (curry c) z t)
2126
2127
2127
2128
-- | /O(n)/ Construct a map with the supplied mappings. If the list
2128
2129
-- 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 '
2131
2132
{-# INLINABLE fromList #-}
2132
2133
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
+
2133
2139
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
2134
2140
-- the provided function @f@ to merge duplicate entries with
2135
2141
-- @(f newVal oldVal)@.
@@ -2160,10 +2166,15 @@ fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty'
2160
2166
--
2161
2167
-- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
2162
2168
-- > = 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 '
2165
2171
{-# INLINE fromListWith #-}
2166
2172
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
+
2167
2178
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
2168
2179
-- the provided function to merge duplicate entries.
2169
2180
--
@@ -2190,10 +2201,15 @@ fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
2190
2201
-- > = fromList [(k, f k d (f k c (f k b a)))]
2191
2202
--
2192
2203
-- @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 '
2195
2206
{-# INLINE fromListWithKey #-}
2196
2207
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
+
2197
2213
------------------------------------------------------------------------
2198
2214
-- Array operations
2199
2215
@@ -2378,5 +2394,5 @@ ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y ==# 1#)
2378
2394
-- IsList instance
2379
2395
instance (Eq k , Hashable k , KnownNat salt ) => Exts. IsList (HashMapT salt k v ) where
2380
2396
type Item (HashMapT salt k v ) = (k , v )
2381
- fromList = fromList
2397
+ fromList = fromList'
2382
2398
toList = toList
0 commit comments