[commit: packages/hoopl] master, pr/coverage: Add Functor, Foldable, Traversable instances for LabelMap (dccbc3a)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:37:28 UTC 2017


Repository : ssh://git@git.haskell.org/hoopl

On branches: master,pr/coverage
Link       : http://git.haskell.org/packages/hoopl.git/commitdiff/dccbc3aa74d70a5cca118a2735bda1bc09cdffe5

>---------------------------------------------------------------

commit dccbc3aa74d70a5cca118a2735bda1bc09cdffe5
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Mon Mar 28 15:23:44 2016 +0200

    Add Functor, Foldable, Traversable instances for LabelMap


>---------------------------------------------------------------

dccbc3aa74d70a5cca118a2735bda1bc09cdffe5
 src/Compiler/Hoopl/Label.hs  | 8 +++++++-
 src/Compiler/Hoopl/Unique.hs | 8 +++++++-
 2 files changed, 14 insertions(+), 2 deletions(-)

diff --git a/src/Compiler/Hoopl/Label.hs b/src/Compiler/Hoopl/Label.hs
index a1c890a..0f6c753 100644
--- a/src/Compiler/Hoopl/Label.hs
+++ b/src/Compiler/Hoopl/Label.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE CPP, TypeFamilies #-}
+{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
 #if __GLASGOW_HASKELL__ >= 701
 {-# LANGUAGE Safe #-}
 #endif
@@ -17,6 +18,10 @@ where
 
 import Compiler.Hoopl.Collections
 import Compiler.Hoopl.Unique
+#if !MIN_VERSION_base(4,8,0)
+import Data.Traversable (Traversable)
+import Data.Foldable (Foldable)
+#endif
 
 -----------------------------------------------------------------------------
 --		Label
@@ -64,7 +69,8 @@ instance IsSet LabelSet where
 -----------------------------------------------------------------------------
 -- LabelMap
 
-newtype LabelMap v = LM (UniqueMap v) deriving (Eq, Ord, Show)
+newtype LabelMap v = LM (UniqueMap v)
+  deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
 
 instance IsMap LabelMap where
   type KeyOf LabelMap = Label
diff --git a/src/Compiler/Hoopl/Unique.hs b/src/Compiler/Hoopl/Unique.hs
index 79a7c7c..ca2ca7a 100644
--- a/src/Compiler/Hoopl/Unique.hs
+++ b/src/Compiler/Hoopl/Unique.hs
@@ -1,4 +1,5 @@
 {-# LANGUAGE CPP, TypeFamilies #-}
+{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
 #if __GLASGOW_HASKELL__ >= 709
 {-# LANGUAGE Safe #-}
 #elif __GLASGOW_HASKELL__ >= 701
@@ -26,6 +27,10 @@ import qualified Data.IntSet as S
 
 import Control.Applicative as AP
 import Control.Monad (ap,liftM)
+#if !MIN_VERSION_base(4,8,0)
+import Data.Traversable (Traversable)
+import Data.Foldable (Foldable)
+#endif
 
 -----------------------------------------------------------------------------
 --		Unique
@@ -69,7 +74,8 @@ instance IsSet UniqueSet where
 -----------------------------------------------------------------------------
 -- UniqueMap
 
-newtype UniqueMap v = UM (M.IntMap v) deriving (Eq, Ord, Show)
+newtype UniqueMap v = UM (M.IntMap v)
+  deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
 
 instance IsMap UniqueMap where
   type KeyOf UniqueMap = Unique



More information about the ghc-commits mailing list