[commit: ghc] master: Do not say we cannot when we clearly can (fa9dd06)

git at git.haskell.org git at git.haskell.org
Fri Aug 29 16:54:11 UTC 2014


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

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

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

commit fa9dd0679ec6b75a22213433e860ccb39e89b975
Author: Gabor Greif <ggreif at gmail.com>
Date:   Thu Aug 28 19:14:39 2014 +0200

    Do not say we cannot when we clearly can


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

fa9dd0679ec6b75a22213433e860ccb39e89b975
 .../indexed-types/should_compile/red-black-delete.hs   | 18 +++---------------
 1 file changed, 3 insertions(+), 15 deletions(-)

diff --git a/testsuite/tests/indexed-types/should_compile/red-black-delete.hs b/testsuite/tests/indexed-types/should_compile/red-black-delete.hs
index 9873463..c1ce0fb 100644
--- a/testsuite/tests/indexed-types/should_compile/red-black-delete.hs
+++ b/testsuite/tests/indexed-types/should_compile/red-black-delete.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE InstanceSigs,GADTs, DataKinds, KindSignatures, MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
+{-# LANGUAGE InstanceSigs, GADTs, StandaloneDeriving, DataKinds, KindSignatures, MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
 
 -- Implementation of deletion for red black trees by Matt Might
 -- Editing to preserve the red/black tree invariants by Stephanie Weirich,
@@ -12,7 +12,6 @@
 module MightRedBlackGADT where
 
 import Prelude hiding (max)
--- import Test.QuickCheck hiding (elements)
 import Data.List(nub,sort)
 import Control.Monad(liftM)
 import Data.Type.Equality
@@ -61,19 +60,8 @@ type instance Incr NegativeBlack (S n) = n
 data RBSet a where
   Root :: (CT n Black a) -> RBSet a
 
--- We can't automatically derive show and equality
--- methods for GADTs.
-instance Show (SColor c) where
-  show R = "R"
-  show B = "B"
-  show BB = "BB"
-  show NB = "NB"
-
-instance Show a => Show (CT n c a) where
-  show E = "E"
-  show (T c l x r) =
-    "(T " ++ show c ++ " " ++ show l ++ " "
-          ++ show x ++ " " ++ show r ++ ")"
+deriving instance Show (SColor c)
+deriving instance Show a => Show (CT n c a)
 instance Show a => Show (RBSet a) where
   show (Root x) = show x
 



More information about the ghc-commits mailing list