[commit: ghc] wip/T9732: #stash (2e550dd)
git at git.haskell.org
git at git.haskell.org
Sat Nov 8 08:55:50 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T9732
Link : http://ghc.haskell.org/trac/ghc/changeset/2e550dd4caba298e380e597a1ee55d4f4e652045/ghc
>---------------------------------------------------------------
commit 2e550dd4caba298e380e597a1ee55d4f4e652045
Author: Dr. ERDI Gergo <gergo at erdi.hu>
Date: Fri Nov 7 19:07:40 2014 +0800
#stash
>---------------------------------------------------------------
2e550dd4caba298e380e597a1ee55d4f4e652045
compiler/basicTypes/PatSyn.lhs | 2 +-
compiler/iface/MkIface.lhs | 2 +-
compiler/iface/TcIface.lhs | 3 ++-
compiler/main/TidyPgm.lhs | 5 +++--
4 files changed, 7 insertions(+), 5 deletions(-)
diff --git a/compiler/basicTypes/PatSyn.lhs b/compiler/basicTypes/PatSyn.lhs
index aa33efa..e862d88 100644
--- a/compiler/basicTypes/PatSyn.lhs
+++ b/compiler/basicTypes/PatSyn.lhs
@@ -296,7 +296,7 @@ tidyPatSynIds tidy_fn ps@(MkPatSyn { psMatcher = match_id, psWrapperWorker = mb_
= ps { psMatcher = tidy_fn match_id, psWrapperWorker = fmap tidy_ww mb_ww }
where
tidy_ww (wrapper, Nothing) = (tidy_fn wrapper, Nothing)
- tidy_ww (wrapper, Just worker) = (wrapper, Just (tidy_fn worker))
+ tidy_ww (wrapper, Just worker) = (tidy_fn wrapper, Just (tidy_fn worker))
patSynInstArgTys :: PatSyn -> [Type] -> [Type]
-- Return the types of the argument patterns
diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs
index 436356b..c11e62c 100644
--- a/compiler/iface/MkIface.lhs
+++ b/compiler/iface/MkIface.lhs
@@ -262,7 +262,7 @@ mkIface_ hsc_env maybe_old_fingerprint
usages <- mkUsageInfo hsc_env this_mod dir_imp_mods used_names dependent_files
let entities = typeEnvElts type_env
- decls = pprTrace "entities" (ppr entities) $
+ decls = pprTrace "entities" (ppr type_env) $
[ tyThingToIfaceDecl entity
| entity <- entities,
let name = getName entity,
diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs
index 801037a..61e169c 100644
--- a/compiler/iface/TcIface.lhs
+++ b/compiler/iface/TcIface.lhs
@@ -281,7 +281,8 @@ typecheckIface iface
-- no global envt for the current interface; instead, the knot is tied
-- through the if_rec_types field of IfGblEnv
; names_w_things <- loadDecls ignore_prags (mi_decls iface)
- ; let type_env = mkNameEnv names_w_things
+ ; let type_env = pprTrace "names_w_things" (ppr names_w_things) $
+ mkNameEnv names_w_things
; writeMutVar tc_env_var type_env
-- Now do those rules, instances and annotations
diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs
index b7a867d..bccb195 100644
--- a/compiler/main/TidyPgm.lhs
+++ b/compiler/main/TidyPgm.lhs
@@ -340,8 +340,9 @@ tidyProgram hsc_env (ModGuts { mg_module = mod
; (tidy_env, tidy_binds)
<- tidyTopBinds hsc_env mod unfold_env tidy_occ_env trimmed_binds
- ; let { final_ids = [ id | id <- bindersOfBinds tidy_binds,
- isExternalName (idName id)]
+ ; let { final_ids = pprTrace "unfold_env" (ppr unfold_env) $
+ [ id | id <- bindersOfBinds tidy_binds,
+ pprTrace "final_id" (ppr id) $ isExternalName (idName id)]
; type_env1 = extendTypeEnvWithIds type_env final_ids
; tidy_insts = map (tidyClsInstDFun (lookup_aux_id tidy_type_env)) insts
More information about the ghc-commits
mailing list