[commit: packages/containers] develop, develop-0.6, develop-0.6-questionable, master, zip-devel: Add IsList instances for OverloadedLists (0e99ba8)
git at git.haskell.org
git at git.haskell.org
Fri Jan 23 22:39:44 UTC 2015
Repository : ssh://git@git.haskell.org/containers
On branches: develop,develop-0.6,develop-0.6-questionable,master,zip-devel
Link : http://git.haskell.org/packages/containers.git/commitdiff/0e99ba8851f875c4b44631c7afad3b70e74842c2
>---------------------------------------------------------------
commit 0e99ba8851f875c4b44631c7afad3b70e74842c2
Author: Konstantine Rybnikov <k-bx at k-bx.com>
Date: Sun Apr 13 22:27:39 2014 +0200
Add IsList instances for OverloadedLists
>---------------------------------------------------------------
0e99ba8851f875c4b44631c7afad3b70e74842c2
Data/IntMap/Base.hs | 16 +++++++++++++++-
Data/IntSet/Base.hs | 13 +++++++++++++
Data/Map/Base.hs | 13 +++++++++++++
Data/Set/Base.hs | 13 +++++++++++++
4 files changed, 54 insertions(+), 1 deletion(-)
diff --git a/Data/IntMap/Base.hs b/Data/IntMap/Base.hs
index 34a263a..75b3ae9 100644
--- a/Data/IntMap/Base.hs
+++ b/Data/IntMap/Base.hs
@@ -5,6 +5,10 @@
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
+{-# LANGUAGE ScopedTypeVariables #-}
+#if __GLASGOW_HASKELL__ >= 708
+{-# LANGUAGE TypeFamilies #-}
+#endif
-----------------------------------------------------------------------------
-- |
-- Module : Data.IntMap.Base
@@ -231,6 +235,9 @@ import Data.StrictPair
import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix),
DataType, mkDataType)
import GHC.Exts (build)
+#if __GLASGOW_HASKELL__ >= 708
+import qualified GHC.Exts as GHCExts
+#endif
import Text.Read
#endif
@@ -1770,6 +1777,13 @@ fromSet f (IntSet.Tip kx bm) = buildTree f kx bm (IntSet.suffixBitMask + 1)
{--------------------------------------------------------------------
Lists
--------------------------------------------------------------------}
+#if __GLASGOW_HASKELL__ >= 708
+instance GHCExts.IsList (IntMap a) where
+ type Item (IntMap a) = (Key,a)
+ fromList = fromList
+ toList = toList
+#endif
+
-- | /O(n)/. Convert the map to a list of key\/value pairs. Subject to list
-- fusion.
--
@@ -1907,7 +1921,7 @@ fromAscListWithKey f (x0 : xs0) = fromDistinctAscList (combineEq x0 xs0)
--
-- > fromDistinctAscList [(3,"b"), (5,"a")] == fromList [(3, "b"), (5, "a")]
-fromDistinctAscList :: [(Key,a)] -> IntMap a
+fromDistinctAscList :: forall a. [(Key,a)] -> IntMap a
fromDistinctAscList [] = Nil
fromDistinctAscList (z0 : zs0) = work z0 zs0 Nada
where
diff --git a/Data/IntSet/Base.hs b/Data/IntSet/Base.hs
index be41db5..0063c3f 100644
--- a/Data/IntSet/Base.hs
+++ b/Data/IntSet/Base.hs
@@ -5,6 +5,9 @@
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
+#if __GLASGOW_HASKELL__ >= 708
+{-# LANGUAGE TypeFamilies #-}
+#endif
-----------------------------------------------------------------------------
-- |
-- Module : Data.IntSet.Base
@@ -198,6 +201,9 @@ import Text.Read
#if __GLASGOW_HASKELL__
import GHC.Exts (Int(..), build)
+#if __GLASGOW_HASKELL__ >= 708
+import qualified GHC.Exts as GHCExts
+#endif
import GHC.Prim (indexInt8OffAddr#)
#endif
@@ -936,6 +942,13 @@ elems
{--------------------------------------------------------------------
Lists
--------------------------------------------------------------------}
+#if __GLASGOW_HASKELL__ >= 708
+instance GHCExts.IsList IntSet where
+ type Item IntSet = Key
+ fromList = fromList
+ toList = toList
+#endif
+
-- | /O(n)/. Convert the set to a list of elements. Subject to list fusion.
toList :: IntSet -> [Key]
toList
diff --git a/Data/Map/Base.hs b/Data/Map/Base.hs
index 6a93a73..69f8276 100644
--- a/Data/Map/Base.hs
+++ b/Data/Map/Base.hs
@@ -5,6 +5,9 @@
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
+#if __GLASGOW_HASKELL__ >= 708
+{-# LANGUAGE TypeFamilies #-}
+#endif
-----------------------------------------------------------------------------
-- |
-- Module : Data.Map.Base
@@ -278,6 +281,9 @@ import qualified Data.Set.Base as Set
#if __GLASGOW_HASKELL__
import GHC.Exts ( build )
+#if __GLASGOW_HASKELL__ >= 708
+import qualified GHC.Exts as GHCExts
+#endif
import Text.Read
import Data.Data
#endif
@@ -1948,6 +1954,13 @@ fromSet f (Set.Bin sz x l r) = Bin sz x (f x) (fromSet f l) (fromSet f r)
Lists
use [foldlStrict] to reduce demand on the control-stack
--------------------------------------------------------------------}
+#if __GLASGOW_HASKELL__ >= 708
+instance (Ord k) => GHCExts.IsList (Map k v) where
+ type Item (Map k v) = (k,v)
+ fromList = fromList
+ toList = toList
+#endif
+
-- | /O(n*log n)/. Build a map from a list of key\/value pairs. See also 'fromAscList'.
-- If the list contains more than one value for the same key, the last value
-- for the key is retained.
diff --git a/Data/Set/Base.hs b/Data/Set/Base.hs
index f863d17..94372df 100644
--- a/Data/Set/Base.hs
+++ b/Data/Set/Base.hs
@@ -5,6 +5,9 @@
#if !defined(TESTING) && __GLASGOW_HASKELL__ >= 703
{-# LANGUAGE Trustworthy #-}
#endif
+#if __GLASGOW_HASKELL__ >= 708
+{-# LANGUAGE TypeFamilies #-}
+#endif
-----------------------------------------------------------------------------
-- |
-- Module : Data.Set.Base
@@ -194,6 +197,9 @@ import Data.StrictPair
#if __GLASGOW_HASKELL__
import GHC.Exts ( build )
+#if __GLASGOW_HASKELL__ >= 708
+import qualified GHC.Exts as GHCExts
+#endif
import Text.Read
import Data.Data
#endif
@@ -763,6 +769,13 @@ elems = toAscList
{--------------------------------------------------------------------
Lists
--------------------------------------------------------------------}
+#if __GLASGOW_HASKELL__ >= 708
+instance (Ord a) => GHCExts.IsList (Set a) where
+ type Item (Set a) = a
+ fromList = fromList
+ toList = toList
+#endif
+
-- | /O(n)/. Convert the set to a list of elements. Subject to list fusion.
toList :: Set a -> [a]
toList = toAscList
More information about the ghc-commits
mailing list