Skip to content

Commit 1447081

Browse files
committed
IsList instances for GHC ≥ 7.8
1 parent 599128b commit 1447081

File tree

2 files changed

+41
-2
lines changed

2 files changed

+41
-2
lines changed

Data/HashMap/Base.hs

Lines changed: 27 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,8 @@
11
{-# LANGUAGE BangPatterns, CPP, DeriveDataTypeable, MagicHash #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
3+
#if __GLASGOW_HASKELL__ >= 708
4+
{-# LANGUAGE TypeFamilies #-}
5+
#endif
26
{-# OPTIONS_GHC -fno-full-laziness -funbox-strict-fields #-}
37

48
module Data.HashMap.Base
@@ -101,6 +105,9 @@ import Data.Typeable (Typeable)
101105
#if __GLASGOW_HASKELL__ >= 707
102106
import GHC.Exts (isTrue#)
103107
#endif
108+
#if __GLASGOW_HASKELL__ >= 708
109+
import qualified GHC.Exts as Exts
110+
#endif
104111

105112

106113
------------------------------------------------------------------------
@@ -433,11 +440,14 @@ insertWith f k0 v0 m0 = go h0 k0 v0 0 m0
433440
{-# INLINABLE insertWith #-}
434441

435442
-- | In-place update version of insertWith
436-
unsafeInsertWith :: (Eq k, Hashable k) => (v -> v -> v) -> k -> v -> HashMap k v
443+
unsafeInsertWith :: forall k v. (Eq k, Hashable k)
444+
=> (v -> v -> v) -> k -> v -> HashMap k v
437445
-> HashMap k v
438446
unsafeInsertWith f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
439447
where
440448
h0 = hash k0
449+
go :: (Eq k, Hashable k) => Hash -> k -> v -> Shift -> HashMap k v
450+
-> ST s (HashMap k v)
441451
go !h !k x !_ Empty = return $! Leaf h (L k x)
442452
go h k x s (Leaf hy l@(L ky y))
443453
| hy == h = if ky == k
@@ -813,7 +823,7 @@ trim mary n = do
813823

814824
-- | /O(n)/ Filter this map by retaining only elements satisfying a
815825
-- predicate.
816-
filterWithKey :: (k -> v -> Bool) -> HashMap k v -> HashMap k v
826+
filterWithKey :: forall k v. (k -> v -> Bool) -> HashMap k v -> HashMap k v
817827
filterWithKey pred = go
818828
where
819829
go Empty = Empty
@@ -830,6 +840,9 @@ filterWithKey pred = go
830840
mary <- A.new_ n
831841
step ary0 mary b0 0 0 1 n
832842
where
843+
step :: A.Array (HashMap k v) -> A.MArray s (HashMap k v)
844+
-> Bitmap -> Int -> Int -> Bitmap -> Int
845+
-> ST s (HashMap k v)
833846
step !ary !mary !b i !j !bi n
834847
| i >= n = case j of
835848
0 -> return Empty
@@ -856,6 +869,9 @@ filterWithKey pred = go
856869
mary <- A.new_ n
857870
step ary0 mary 0 0 n
858871
where
872+
step :: A.Array (Leaf k v) -> A.MArray s (Leaf k v)
873+
-> Int -> Int -> Int
874+
-> ST s (HashMap k v)
859875
step !ary !mary i !j n
860876
| i >= n = case j of
861877
0 -> return Empty
@@ -1085,3 +1101,12 @@ ptrEq x y = reallyUnsafePtrEquality# x y ==# 1#
10851101
ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y ==# 1#)
10861102
#endif
10871103
{-# INLINE ptrEq #-}
1104+
1105+
#if __GLASGOW_HASKELL__ >= 708
1106+
------------------------------------------------------------------------
1107+
-- IsList instance
1108+
instance (Eq k, Hashable k) => Exts.IsList (HashMap k v) where
1109+
type Item (HashMap k v) = (k, v)
1110+
fromList = fromList
1111+
toList = toList
1112+
#endif

Data/HashSet.hs

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,7 @@
11
{-# LANGUAGE CPP, DeriveDataTypeable #-}
2+
#if __GLASGOW_HASKELL__ >= 708
3+
{-# LANGUAGE TypeFamilies #-}
4+
#endif
25

36
------------------------------------------------------------------------
47
-- |
@@ -71,6 +74,10 @@ import qualified Data.HashMap.Lazy as H
7174
import qualified Data.List as List
7275
import Data.Typeable (Typeable)
7376

77+
#if __GLASGOW_HASKELL__ >= 708
78+
import qualified GHC.Exts as Exts
79+
#endif
80+
7481
-- | A set of values. A set cannot contain duplicate values.
7582
newtype HashSet a = HashSet {
7683
asMap :: HashMap a ()
@@ -221,3 +228,10 @@ toList t = build (\ c z -> foldrWithKey ((const .) c) z (asMap t))
221228
fromList :: (Eq a, Hashable a) => [a] -> HashSet a
222229
fromList = HashSet . List.foldl' (\ m k -> H.insert k () m) H.empty
223230
{-# INLINE fromList #-}
231+
232+
#if __GLASGOW_HASKELL__ >= 708
233+
instance (Eq a, Hashable a) => Exts.IsList (HashSet a) where
234+
type Item (HashSet a) = a
235+
fromList = fromList
236+
toList = toList
237+
#endif

0 commit comments

Comments
 (0)