Skip to content

Commit 1162033

Browse files
committed
Fix minor Api Change, export new HashMapT
1 parent 0741c8a commit 1162033

File tree

3 files changed

+40
-24
lines changed

3 files changed

+40
-24
lines changed

Data/HashMap/Internal.hs

Lines changed: 24 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,9 @@ module Data.HashMap.Internal
3232

3333
-- * Construction
3434
, empty
35+
, empty'
3536
, singleton
37+
, singleton'
3638

3739
-- * Basic interface
3840
, null
@@ -325,7 +327,7 @@ instance (Eq k, Hashable k, KnownNat salt) => Semigroup (HashMapT salt k v) wher
325327
-- >>> mappend (fromList [(1,'a'),(2,'b')]) (fromList [(2,'c'),(3,'d')])
326328
-- fromList [(1,'a'),(2,'b'),(3,'d')]
327329
instance (Eq k, Hashable k, KnownNat salt) => Monoid (HashMapT salt k v) where
328-
mempty = empty
330+
mempty = empty'
329331
{-# INLINE mempty #-}
330332
#if __GLASGOW_HASKELL__ >= 711
331333
mappend = (<>)
@@ -597,12 +599,20 @@ isLeafOrCollision _ = False
597599
-- * Construction
598600

599601
-- | /O(1)/ Construct an empty map.
600-
empty :: forall k v salt . HashMapT salt k v
601-
empty = Empty
602+
empty :: forall k v salt . HashMap k v
603+
empty = empty'
604+
605+
-- | like 'empty' but allows a custom salt to be set
606+
empty' :: forall k v salt . HashMapT salt k v
607+
empty' = Empty
602608

603609
-- | /O(1)/ Construct a map with a single element.
604-
singleton :: forall k v salt . (Hashable k, KnownNat salt) => k -> v -> HashMapT salt k v
605-
singleton k v = Leaf (hash (Proxy :: Proxy salt) k) (L k v)
610+
singleton :: forall k v salt . (Hashable k) => k -> v -> HashMap k v
611+
singleton = singleton'
612+
613+
-- | like 'singleton' but allows a custom salt to be set
614+
singleton' :: forall k v salt . (Hashable k, KnownNat salt) => k -> v -> HashMapT salt k v
615+
singleton' k v = Leaf (hash (Proxy :: Proxy salt) k) (L k v)
606616

607617
------------------------------------------------------------------------
608618
-- * Basic interface
@@ -1728,7 +1738,7 @@ unionArrayBy f b1 b2 ary1 ary2 = A.run $ do
17281738

17291739
-- | Construct a set containing all elements from a list of sets.
17301740
unions :: (Eq k, Hashable k, KnownNat salt) => [HashMapT salt k v] -> HashMapT salt k v
1731-
unions = L.foldl' union empty
1741+
unions = L.foldl' union empty'
17321742
{-# INLINE unions #-}
17331743

17341744

@@ -1824,7 +1834,7 @@ mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
18241834
-- | /O(n*log m)/ Difference of two maps. Return elements of the first map
18251835
-- not existing in the second.
18261836
difference :: (Eq k, Hashable k, KnownNat salt) => HashMapT salt k v -> HashMapT salt k w -> HashMapT salt k v
1827-
difference a b = foldlWithKey' go empty a
1837+
difference a b = foldlWithKey' go empty' a
18281838
where
18291839
go m k v = case lookup k b of
18301840
Nothing -> insert k v m
@@ -1836,7 +1846,7 @@ difference a b = foldlWithKey' go empty a
18361846
-- If it returns 'Nothing', the element is discarded (proper set difference). If
18371847
-- it returns (@'Just' y@), the element is updated with a new value @y@.
18381848
differenceWith :: (Eq k, Hashable k, KnownNat salt) => (v -> w -> Maybe v) -> HashMapT salt k v -> HashMapT salt k w -> HashMapT salt k v
1839-
differenceWith f a b = foldlWithKey' go empty a
1849+
differenceWith f a b = foldlWithKey' go empty' a
18401850
where
18411851
go m k v = case lookup k b of
18421852
Nothing -> insert k v m
@@ -1846,7 +1856,7 @@ differenceWith f a b = foldlWithKey' go empty a
18461856
-- | /O(n*log m)/ Intersection of two maps. Return elements of the first
18471857
-- map for keys existing in the second.
18481858
intersection :: (Eq k, Hashable k, KnownNat salt) => HashMapT salt k v -> HashMapT salt k w -> HashMapT salt k v
1849-
intersection a b = foldlWithKey' go empty a
1859+
intersection a b = foldlWithKey' go empty' a
18501860
where
18511861
go m k v = case lookup k b of
18521862
Just _ -> insert k v m
@@ -1858,7 +1868,7 @@ intersection a b = foldlWithKey' go empty a
18581868
-- maps.
18591869
intersectionWith :: (Eq k, Hashable k, KnownNat salt) => (v1 -> v2 -> v3) -> HashMapT salt k v1
18601870
-> HashMapT salt k v2 -> HashMapT salt k v3
1861-
intersectionWith f a b = foldlWithKey' go empty a
1871+
intersectionWith f a b = foldlWithKey' go empty' a
18621872
where
18631873
go m k v = case lookup k b of
18641874
Just w -> insert k (f v w) m
@@ -1870,7 +1880,7 @@ intersectionWith f a b = foldlWithKey' go empty a
18701880
-- maps.
18711881
intersectionWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v1 -> v2 -> v3)
18721882
-> HashMapT salt k v1 -> HashMapT salt k v2 -> HashMapT salt k v3
1873-
intersectionWithKey f a b = foldlWithKey' go empty a
1883+
intersectionWithKey f a b = foldlWithKey' go empty' a
18741884
where
18751885
go m k v = case lookup k b of
18761886
Just w -> insert k (f k v w) m
@@ -2117,7 +2127,7 @@ toList t = build (\ c z -> foldrWithKey (curry c) z t)
21172127
-- | /O(n)/ Construct a map with the supplied mappings. If the list
21182128
-- contains duplicate mappings, the later mappings take precedence.
21192129
fromList :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
2120-
fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty
2130+
fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty'
21212131
{-# INLINABLE fromList #-}
21222132

21232133
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
@@ -2151,7 +2161,7 @@ fromList = L.foldl' (\ m (k, v) -> unsafeInsert k v m) empty
21512161
-- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
21522162
-- > = fromList [(k, f d (f c (f b a)))]
21532163
fromListWith :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2154-
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
2164+
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
21552165
{-# INLINE fromListWith #-}
21562166

21572167
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
@@ -2181,7 +2191,7 @@ fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
21812191
--
21822192
-- @since 0.2.11
21832193
fromListWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
2184-
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty
2194+
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
21852195
{-# INLINE fromListWithKey #-}
21862196

21872197
------------------------------------------------------------------------

Data/HashMap/Internal/Strict.hs

Lines changed: 14 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,7 @@ module Data.HashMap.Internal.Strict
4444
-- $strictness
4545

4646
HashMap
47+
, HashMapT
4748

4849
-- * Construction
4950
, empty
@@ -132,7 +133,7 @@ import qualified Data.HashMap.Internal.Array as A
132133
import qualified Data.HashMap.Internal as HM
133134
import Data.HashMap.Internal hiding (
134135
alter, alterF, adjust, fromList, fromListWith, fromListWithKey,
135-
insert, insertWith,
136+
insert, insertWith, singleton',
136137
differenceWith, intersectionWith, intersectionWithKey, map, mapWithKey,
137138
mapMaybe, mapMaybeWithKey, singleton, update, unionWith, unionWithKey,
138139
traverseWithKey)
@@ -158,8 +159,12 @@ import Data.Proxy(Proxy(..))
158159
-- * Construction
159160

160161
-- | /O(1)/ Construct a map with a single element.
161-
singleton :: (Hashable k, KnownNat salt) => k -> v -> HashMapT salt k v
162-
singleton k !v = HM.singleton k v
162+
singleton :: (Hashable k) => k -> v -> HashMap k v
163+
singleton = singleton'
164+
165+
-- | like 'singleton' but allows a custom salt to be set
166+
singleton' :: (Hashable k, KnownNat salt) => k -> v -> HashMapT salt k v
167+
singleton' k !v = HM.singleton' k v
163168

164169
------------------------------------------------------------------------
165170
-- * Basic interface
@@ -600,7 +605,7 @@ traverseWithKey f = go
600605
-- If it returns 'Nothing', the element is discarded (proper set difference). If
601606
-- it returns (@'Just' y@), the element is updated with a new value @y@.
602607
differenceWith :: (Eq k, Hashable k, KnownNat salt) => (v -> w -> Maybe v) -> HashMapT salt k v -> HashMapT salt k w -> HashMapT salt k v
603-
differenceWith f a b = foldlWithKey' go empty a
608+
differenceWith f a b = foldlWithKey' go empty' a
604609
where
605610
go m k v = case HM.lookup k b of
606611
Nothing -> insert k v m
@@ -612,7 +617,7 @@ differenceWith f a b = foldlWithKey' go empty a
612617
-- maps.
613618
intersectionWith :: (Eq k, Hashable k, KnownNat salt) => (v1 -> v2 -> v3) -> HashMapT salt k v1
614619
-> HashMapT salt k v2 -> HashMapT salt k v3
615-
intersectionWith f a b = foldlWithKey' go empty a
620+
intersectionWith f a b = foldlWithKey' go empty' a
616621
where
617622
go m k v = case HM.lookup k b of
618623
Just w -> insert k (f v w) m
@@ -624,7 +629,7 @@ intersectionWith f a b = foldlWithKey' go empty a
624629
-- maps.
625630
intersectionWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v1 -> v2 -> v3)
626631
-> HashMapT salt k v1 -> HashMapT salt k v2 -> HashMapT salt k v3
627-
intersectionWithKey f a b = foldlWithKey' go empty a
632+
intersectionWithKey f a b = foldlWithKey' go empty' a
628633
where
629634
go m k v = case HM.lookup k b of
630635
Just w -> insert k (f k v w) m
@@ -638,7 +643,7 @@ intersectionWithKey f a b = foldlWithKey' go empty a
638643
-- list contains duplicate mappings, the later mappings take
639644
-- precedence.
640645
fromList :: (Eq k, Hashable k, KnownNat salt) => [(k, v)] -> HashMapT salt k v
641-
fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty
646+
fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty'
642647
{-# INLINABLE fromList #-}
643648

644649
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
@@ -672,7 +677,7 @@ fromList = L.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) empty
672677
-- > fromListWith f [(k, a), (k, b), (k, c), (k, d)]
673678
-- > = fromList [(k, f d (f c (f b a)))]
674679
fromListWith :: (Eq k, Hashable k, KnownNat salt) => (v -> v -> v) -> [(k, v)] -> HashMapT salt k v
675-
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
680+
fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty'
676681
{-# INLINE fromListWith #-}
677682

678683
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
@@ -702,7 +707,7 @@ fromListWith f = L.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) empty
702707
--
703708
-- @since 0.2.11
704709
fromListWithKey :: (Eq k, Hashable k, KnownNat salt) => (k -> v -> v -> v) -> [(k, v)] -> HashMapT salt k v
705-
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty
710+
fromListWithKey f = L.foldl' (\ m (k, v) -> unsafeInsertWithKey f k v m) empty'
706711
{-# INLINE fromListWithKey #-}
707712

708713
------------------------------------------------------------------------

Data/HashMap/Strict.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ module Data.HashMap.Strict
2626
-- * Strictness properties
2727
-- $strictness
2828

29-
HashMap
29+
HashMapT
30+
, HashMap
3031

3132
-- * Construction
3233
, empty

0 commit comments

Comments
 (0)