[commit: ghc] wip/Txxxxx: WIP: cleanups (51a1bf0)

git at git.haskell.org git at git.haskell.org
Thu Dec 28 10:00:02 UTC 2017


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

On branch  : wip/Txxxxx
Link       : http://ghc.haskell.org/trac/ghc/changeset/51a1bf064328fc625fdef59262784ab04eb2fec1/ghc

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

commit 51a1bf064328fc625fdef59262784ab04eb2fec1
Author: Gabor Greif <ggreif at gmail.com>
Date:   Thu Dec 28 10:58:55 2017 +0100

    WIP: cleanups
    
    and add TODO
    
    (also this should be more performant, by consing less)


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

51a1bf064328fc625fdef59262784ab04eb2fec1
 compiler/codeGen/StgCmmClosure.hs | 17 ++++++-----------
 1 file changed, 6 insertions(+), 11 deletions(-)

diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs
index feb9987..39d156f 100644
--- a/compiler/codeGen/StgCmmClosure.hs
+++ b/compiler/codeGen/StgCmmClosure.hs
@@ -1,5 +1,5 @@
-{-# LANGUAGE CPP, RecordWildCards, StandaloneDeriving #-}
-{-# OPTIONS_GHC -Wno-orphans #-}
+{-# LANGUAGE CPP, RecordWildCards #-}
+
 -----------------------------------------------------------------------------
 --
 -- Stg to C-- code generation:
@@ -223,13 +223,8 @@ 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
@@ -586,9 +581,9 @@ getCallMethod dflags name id (LFReEntrant _ _ arity _ _) n_args _v_args _cg_loc
 getCallMethod _ _name _ LFUnlifted n_args _v_args _cg_loc _self_loop_info
   = ASSERT( n_args == 0 ) ReturnIt
 
-getCallMethod _ name id (LFUnknown False) 0 _v_args cg_loc _self_loop_info
-  | occNameString (nameOccName name) == "wild"
-  = pprTrace "getCallMethod" (ppr id <+> ppr cg_loc) ReturnIt
+getCallMethod _ name _ (LFUnknown False) 0 _v_args cg_loc _self_loop_info
+  | occNameString (nameOccName name) == "wild" -- TODO: make this robust
+  = ReturnIt -- seems to come from case, must be (tagged) WHNF already
 
 getCallMethod _ _name _ (LFCon _) n_args _v_args _cg_loc _self_loop_info
   = ASSERT( n_args == 0 ) ReturnIt



More information about the ghc-commits mailing list