[commit: ghc] wip/T14373: debugging... (172b555)
git at git.haskell.org
git at git.haskell.org
Wed Dec 13 21:32:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T14373
Link : http://ghc.haskell.org/trac/ghc/changeset/172b5555a89a3b664cea2a623411bc5d29d3e9e5/ghc
>---------------------------------------------------------------
commit 172b5555a89a3b664cea2a623411bc5d29d3e9e5
Author: Gabor Greif <ggreif at gmail.com>
Date: Thu Dec 7 17:25:19 2017 +0100
debugging...
>---------------------------------------------------------------
172b5555a89a3b664cea2a623411bc5d29d3e9e5
compiler/stgSyn/CoreToStg.hs | 11 +++++++++--
1 file changed, 9 insertions(+), 2 deletions(-)
diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs
index 900c52e..bd4f1a6 100644
--- a/compiler/stgSyn/CoreToStg.hs
+++ b/compiler/stgSyn/CoreToStg.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns, CPP, MagicHash #-}
--
-- (c) The GRASP/AQUA Project, Glasgow University, 1993-1998
@@ -49,6 +49,13 @@ import UniqFM
import Data.Maybe (isJust, fromMaybe)
import Control.Monad (liftM, ap)
+import Debug.Trace (traceShowId)
+import GHC.Base (getTag)
+import GHC.Exts (Int(..))
+
+
+instance Show IdDetails where
+ show !det = "## we have an IdDetails with tag " ++ show (I# (getTag det))
-- Note [Live vs free]
-- ~~~~~~~~~~~~~~~~~~~
@@ -540,7 +547,7 @@ coreToStgApp _ f args ticks = do
| otherwise = stgUnsatOcc -- Unsaturated function or thunk
res_ty = exprType (mkApps (Var f) args)
- app = case idDetails f of
+ app = case traceShowId $ idDetails f of
DataConWorkId dc
| saturated -> StgConApp dc args'
(dropRuntimeRepArgs (fromMaybe [] (tyConAppArgs_maybe res_ty)))
More information about the ghc-commits
mailing list