[commit: ghc] wip/T13861: Revert "WIP: clean up some cruft" (a67a28d)

git at git.haskell.org git at git.haskell.org
Wed Jan 3 16:11:01 UTC 2018


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

On branch  : wip/T13861
Link       : http://ghc.haskell.org/trac/ghc/changeset/a67a28d26584511d78ddd6c8ece7191a04f3101b/ghc

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

commit a67a28d26584511d78ddd6c8ece7191a04f3101b
Author: Gabor Greif <ggreif at gmail.com>
Date:   Wed Jan 3 11:26:26 2018 +0100

    Revert "WIP: clean up some cruft"
    
    This reverts commit a0fdeba207e457924a2b7204dd4f7db14d5e4364.


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

a67a28d26584511d78ddd6c8ece7191a04f3101b
 compiler/codeGen/StgCmmClosure.hs | 11 ++++++++---
 1 file changed, 8 insertions(+), 3 deletions(-)

diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs
index 8c49628..9de4f9d 100644
--- a/compiler/codeGen/StgCmmClosure.hs
+++ b/compiler/codeGen/StgCmmClosure.hs
@@ -1,5 +1,5 @@
-{-# LANGUAGE CPP, RecordWildCards #-}
-
+{-# LANGUAGE CPP, RecordWildCards, StandaloneDeriving #-}
+{-# OPTIONS_GHC -Wno-orphans #-}
 -----------------------------------------------------------------------------
 --
 -- Stg to C-- code generation:
@@ -224,8 +224,13 @@ data LambdaFormInfo
                         -- always a value, needs evaluation
 
   | LFLetNoEscape       -- See LetNoEscape module for precise description
+ deriving Show
 
-
+deriving instance Show TopLevelFlag
+deriving instance Show OneShotInfo
+deriving instance Show ArgDescr
+deriving instance Show StandardFormInfo
+instance Show DataCon where show _ = "<DATACON>"
 -------------------------
 -- StandardFormInfo tells whether this thunk has one of
 -- a small number of standard forms



More information about the ghc-commits mailing list