Skip to content
Snippets Groups Projects
Commit 2558ec22 authored by Jeff Lewis's avatar Jeff Lewis
Browse files

[project @ 2000-05-14 07:16:50 by lewie]

Wobble.  Fine tuning tcSimplifyAndCheck a bit further (wrt implicit params).
The key is that a method that doesn't constrain a local tyvar, but does has
implicit params, needs to be reduced further.
parent 6f122ef3
No related merge requests found
......@@ -25,7 +25,8 @@ module Inst (
lookupInst, lookupSimpleInst, LookupInstResult(..),
isDict, isClassDict, isTyVarDict, isStdClassTyVarDict, isMethodFor, notFunDep,
isDict, isClassDict, isMethod,
isTyVarDict, isStdClassTyVarDict, isMethodFor, notFunDep,
instBindingRequired, instCanBeGeneralised,
zonkInst, zonkInsts, zonkFunDeps, zonkTvFunDeps,
......@@ -302,10 +303,14 @@ Predicates
\begin{code}
isDict :: Inst -> Bool
isDict (Dict _ _ _) = True
isDict other = False
isDict other = False
isClassDict :: Inst -> Bool
isClassDict (Dict _ (Class _ _) _) = True
isClassDict other = False
isClassDict other = False
isMethod :: Inst -> Bool
isMethod (Method _ _ _ _ _ _) = True
isMethod other = False
isMethodFor :: TcIdSet -> Inst -> Bool
isMethodFor ids (Method uniq id tys _ _ loc)
......@@ -574,10 +579,10 @@ pprInst (Dict u pred loc) = pprPred pred <+> show_uniq u
pprInst m@(Method u id tys theta tau loc)
= hsep [ppr id, ptext SLIT("at"),
brackets (interppSP tys),
brackets (interppSP tys) {- ,
ppr theta, ppr tau,
show_uniq u,
ppr (instToId m)]
ppr (instToId m) -}]
pprInst (FunDep clas fds loc)
= hsep [ppr clas, ppr fds]
......
......@@ -132,7 +132,7 @@ import TcHsSyn ( TcExpr, TcId,
import TcMonad
import Inst ( lookupInst, lookupSimpleInst, LookupInstResult(..),
tyVarsOfInst, tyVarsOfInsts,
isDict, isClassDict, isStdClassTyVarDict,
isDict, isClassDict, isMethod, isStdClassTyVarDict,
isMethodFor, notFunDep,
instToId, instBindingRequired, instCanBeGeneralised,
newDictFromOld,
......@@ -299,6 +299,7 @@ tcSimplifyAndCheck str local_tvs given_lie wanted_lie
try_me inst
-- Does not constrain a local tyvar
| isEmptyVarSet (tyVarsOfInst inst `intersectVarSet` local_tvs)
&& (not (isMethod inst) || null (getIPs inst))
= Free
-- When checking against a given signature we always reduce
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment