[commit: ghc] master: Role problems pervent GND from happening (75c211e)

git at git.haskell.org git at git.haskell.org
Wed Dec 17 12:27:03 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/75c211ecafad890854f4a1f3e527bd42b13fc516/ghc

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

commit 75c211ecafad890854f4a1f3e527bd42b13fc516
Author: Gabor Greif <ggreif at gmail.com>
Date:   Wed Dec 17 12:49:51 2014 +0100

    Role problems pervent GND from happening
    
    with GHC HEAD. Reworked using deriving instance.


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

75c211ecafad890854f4a1f3e527bd42b13fc516
 compiler/utils/UniqFM.hs | 6 +++++-
 1 file changed, 5 insertions(+), 1 deletion(-)

diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs
index 8f962d4..e24c717 100644
--- a/compiler/utils/UniqFM.hs
+++ b/compiler/utils/UniqFM.hs
@@ -23,7 +23,9 @@ of arguments of combining function.
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE DeriveDataTypeable #-}
 {-# LANGUAGE DeriveTraversable #-}
+{-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE StandaloneDeriving #-}
 {-# OPTIONS_GHC -Wall #-}
 
 module UniqFM (
@@ -211,9 +213,11 @@ instance Monoid (UniqFM a) where
 -}
 
 newtype UniqFM ele = UFM (M.IntMap ele)
-  deriving (Data, Eq, Foldable.Foldable, Functor, Traversable.Traversable,
+  deriving (Data, Eq, Functor, Traversable.Traversable,
             Typeable)
 
+deriving instance Foldable.Foldable UniqFM
+
 emptyUFM = UFM M.empty
 isNullUFM (UFM m) = M.null m
 unitUFM k v = UFM (M.singleton (getKey $ getUnique k) v)



More information about the ghc-commits mailing list