[commit: ghc] wip/T14626: WIP: don't reenter WHNF thing for re-tagging (eac9f6c)
git at git.haskell.org
git at git.haskell.org
Sun Jan 28 16:06:10 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T14626
Link : http://ghc.haskell.org/trac/ghc/changeset/eac9f6c8419cc1875c59d87d0f2b13a0dab56ebb/ghc
>---------------------------------------------------------------
commit eac9f6c8419cc1875c59d87d0f2b13a0dab56ebb
Author: Gabor Greif <ggreif at gmail.com>
Date: Wed Dec 27 19:47:50 2017 +0100
WIP: don't reenter WHNF thing for re-tagging
this is a very crude test. How to make it more robust?
>---------------------------------------------------------------
eac9f6c8419cc1875c59d87d0f2b13a0dab56ebb
compiler/codeGen/StgCmmClosure.hs | 15 ++++++++++++---
1 file changed, 12 insertions(+), 3 deletions(-)
diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs
index f64a311..15a123e 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:
@@ -225,8 +225,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
@@ -587,6 +592,10 @@ 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 _ (LFCon _) n_args _v_args _cg_loc _self_loop_info
= ASSERT( n_args == 0 ) ReturnIt
-- n_args=0 because it'd be ill-typed to apply a saturated
More information about the ghc-commits
mailing list