[commit: ghc] master: Derive instance Eq for CmmNode (c0fb187)
Gabor Greif
ggreif at gmail.com
Sat Apr 6 18:30:06 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
https://github.com/ghc/ghc/commit/c0fb187b3cc6722308b4d475151428778502e0dd
>---------------------------------------------------------------
commit c0fb187b3cc6722308b4d475151428778502e0dd
Author: Gabor Greif <ggreif at gmail.com>
Date: Sat Apr 6 18:27:14 2013 +0200
Derive instance Eq for CmmNode
>---------------------------------------------------------------
compiler/cmm/CmmNode.hs | 17 +++--------------
1 file changed, 3 insertions(+), 14 deletions(-)
diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs
index b3adefe..61c0b80 100644
--- a/compiler/cmm/CmmNode.hs
+++ b/compiler/cmm/CmmNode.hs
@@ -1,6 +1,7 @@
-- CmmNode type for representation using Hoopl graphs.
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
+{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS -fno-warn-tabs #-}
@@ -199,20 +200,8 @@ way is done in cmm/CmmOpt.hs currently. We should fix this!
---------------------------------------------
-- Eq instance of CmmNode
--- It is a shame GHC cannot infer it by itself :(
-
-instance Eq (CmmNode e x) where
- (CmmEntry a) == (CmmEntry a') = a==a'
- (CmmComment a) == (CmmComment a') = a==a'
- (CmmAssign a b) == (CmmAssign a' b') = a==a' && b==b'
- (CmmStore a b) == (CmmStore a' b') = a==a' && b==b'
- (CmmUnsafeForeignCall a b c) == (CmmUnsafeForeignCall a' b' c') = a==a' && b==b' && c==c'
- (CmmBranch a) == (CmmBranch a') = a==a'
- (CmmCondBranch a b c) == (CmmCondBranch a' b' c') = a==a' && b==b' && c==c'
- (CmmSwitch a b) == (CmmSwitch a' b') = a==a' && b==b'
- (CmmCall a b c d e f) == (CmmCall a' b' c' d' e' f') = a==a' && b==b' && c==c' && d==d' && e==e' && f==f'
- (CmmForeignCall a b c d e f) == (CmmForeignCall a' b' c' d' e' f') = a==a' && b==b' && c==c' && d==d' && e==e' && f==f'
- _ == _ = False
+
+deriving instance Eq (CmmNode e x)
----------------------------------------------
-- Hoopl instances of CmmNode
More information about the ghc-commits
mailing list