Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
aafdba3b
Commit
aafdba3b
authored
Nov 22, 2007
by
chak@cse.unsw.edu.au.
Browse files
Properly ppr InstEqs in wanteds of implication constraints
parent
97169c5d
Changes
3
Hide whitespace changes
Inline
Side-by-side
compiler/typecheck/Inst.lhs
View file @
aafdba3b
...
...
@@ -603,11 +603,14 @@ pprInst i@(EqInst {tci_left = ty1, tci_right = ty2, tci_co = co})
(\covar -> text "Wanted" <+> ppr (TyVarTy covar) <+> dcolon <+> ppr (EqPred ty1 ty2))
(\co -> text "Given" <+> ppr co <+> dcolon <+> ppr (EqPred ty1 ty2))
pprInst inst = ppr (instName inst) <+> dcolon
<+> (braces (ppr (instType inst)) $$
<+> (braces (ppr (instType inst)
<> implicWantedEqs
) $$
ifPprDebug implic_stuff)
where
implic_stuff | isImplicInst inst = ppr (tci_reft inst)
| otherwise = empty
(implic_stuff, implicWantedEqs)
| isImplicInst inst = (ppr (tci_reft inst),
text " &" <+>
ppr (filter isEqInst (tci_wanted inst)))
| otherwise = (empty, empty)
pprInstInFull inst@(EqInst {}) = pprInst inst
pprInstInFull inst = sep [quotes (pprInst inst), nest 2 (pprInstArising inst)]
...
...
compiler/typecheck/TcRnTypes.lhs
View file @
aafdba3b
...
...
@@ -663,7 +663,7 @@ data Inst
tci_reft :: Refinement,
tci_given :: [Inst], -- Only Dicts and EqInsts
-- (no Methods, LitInsts, ImplicInsts)
tci_wanted :: [Inst], -- Only Dicts and ImplicInsts
tci_wanted :: [Inst], -- Only Dicts
, EqInst,
and ImplicInsts
-- (no Methods or LitInsts)
tci_loc :: InstLoc
...
...
compiler/typecheck/TcSimplify.lhs
View file @
aafdba3b
...
...
@@ -1022,8 +1022,9 @@ makeImplicationBind loc all_tvs reft
pat_rhs = unguardedGRHSs rhs,
pat_rhs_ty = tup_ty,
bind_fvs = placeHolderNames }
; -- pprTrace "Make implic inst" (ppr (implic_inst,irreds,dict_irreds,tup_ty)) $
return ([implic_inst], unitBag (L span bind)) }
; traceTc $ text "makeImplicationBind" <+> ppr implic_inst
; return ([implic_inst], unitBag (L span bind))
}
-----------------------------------------------------------
tryHardCheckLoop :: SDoc
...
...
@@ -1848,7 +1849,7 @@ reduceContext env wanteds
text "----",
text "avails" <+> pprAvails avails,
text "improved =" <+> ppr improved,
text "irreds = " <+> ppr irreds,
text "
(all)
irreds = " <+> ppr
all_
irreds,
text "binds = " <+> ppr binds,
text "needed givens = " <+> ppr needed_givens,
text "----------------------"
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment