X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcExpr.lhs;h=79b097e38a9aab97484833f489166e6c654cb84a;hb=37a6a52facd1c3999ce4472c50b0030568be1e04;hp=297b4e884e924411667c44dd283f13a92c481604;hpb=0c1a685f5727c8516ec3f06806bc3b0ae0be2370;p=ghc-hetmet.git diff --git a/compiler/typecheck/TcExpr.lhs b/compiler/typecheck/TcExpr.lhs index 297b4e8..79b097e 100644 --- a/compiler/typecheck/TcExpr.lhs +++ b/compiler/typecheck/TcExpr.lhs @@ -45,15 +45,18 @@ import Type import Coercion import Var import VarSet +import VarEnv import TysWiredIn import TysPrim( intPrimTy ) import PrimOp( tagToEnumKey ) import PrelNames +import Module import DynFlags import SrcLoc import Util import ListSetOps import Maybes +import ErrUtils import Outputable import FastString import Control.Monad @@ -82,7 +85,7 @@ tcPolyExpr expr res_ty tcPolyExprNC expr res_ty = do { traceTc "tcPolyExprNC" (ppr res_ty) - ; (gen_fn, expr') <- tcGen (GenSkol res_ty) res_ty $ \ _ rho -> + ; (gen_fn, expr') <- tcGen GenSigCtxt res_ty $ \ _ rho -> tcMonoExprNC expr rho ; return (mkLHsWrap gen_fn expr') } @@ -191,7 +194,7 @@ tcExpr (ExprWithTySig expr sig_ty) res_ty -- Remember to extend the lexical type-variable environment ; (gen_fn, expr') - <- tcGen (SigSkol ExprSigCtxt) sig_tc_ty $ \ skol_tvs res_ty -> + <- tcGen ExprSigCtxt sig_tc_ty $ \ skol_tvs res_ty -> tcExtendTyVarEnv2 (hsExplicitTvs sig_ty `zip` mkTyVarTys skol_tvs) $ -- See Note [More instantiated than scoped] in TcBinds tcMonoExprNC expr res_ty @@ -414,8 +417,8 @@ tcExpr (HsIf (Just fun) pred b1 b2) res_ty -- Note [Rebindable syntax for if] -- and it maintains uniformity with other rebindable syntax ; return (HsIf (Just fun') pred' b1' b2') } -tcExpr (HsDo do_or_lc stmts body _) res_ty - = tcDoStmts do_or_lc stmts body res_ty +tcExpr (HsDo do_or_lc stmts _) res_ty + = tcDoStmts do_or_lc stmts res_ty tcExpr (HsProc pat cmd) res_ty = do { (pat', cmd', coi) <- tcProc pat cmd res_ty @@ -737,7 +740,7 @@ tcExpr (PArrSeq _ seq@(FromTo expr1 expr2)) res_ty ; expr1' <- tcPolyExpr expr1 elt_ty ; expr2' <- tcPolyExpr expr2 elt_ty ; enum_from_to <- newMethodFromName (PArrSeqOrigin seq) - enumFromToPName elt_ty + (enumFromToPName basePackageId) elt_ty -- !!!FIXME: chak ; return $ mkHsWrapCoI coi (PArrSeq enum_from_to (FromTo expr1' expr2')) } @@ -747,7 +750,7 @@ tcExpr (PArrSeq _ seq@(FromThenTo expr1 expr2 expr3)) res_ty ; expr2' <- tcPolyExpr expr2 elt_ty ; expr3' <- tcPolyExpr expr3 elt_ty ; eft <- newMethodFromName (PArrSeqOrigin seq) - enumFromThenToPName elt_ty + (enumFromThenToPName basePackageId) elt_ty -- !!!FIXME: chak ; return $ mkHsWrapCoI coi (PArrSeq eft (FromThenTo expr1' expr2' expr3')) } @@ -819,7 +822,8 @@ tcApp fun args res_ty -- Typecheck the result, thereby propagating -- info (if any) from result into the argument types -- Both actual_res_ty and res_ty are deeply skolemised - ; co_res <- unifyType actual_res_ty res_ty + ; co_res <- addErrCtxtM (funResCtxt fun actual_res_ty res_ty) $ + unifyType actual_res_ty res_ty -- Typecheck the arguments ; args1 <- tcArgs fun args expected_arg_tys @@ -1384,6 +1388,24 @@ funAppCtxt fun arg arg_no quotes (ppr fun) <> text ", namely"]) 2 (quotes (ppr arg)) +funResCtxt :: LHsExpr Name -> TcType -> TcType + -> TidyEnv -> TcM (TidyEnv, Message) +-- When we have a mis-match in the return type of a function +-- try to give a helpful message about too many/few arguments +funResCtxt fun fun_res_ty res_ty env0 + = do { fun_res' <- zonkTcType fun_res_ty + ; res' <- zonkTcType res_ty + ; let n_fun = length (fst (tcSplitFunTys fun_res')) + n_res = length (fst (tcSplitFunTys res')) + what | n_fun > n_res = ptext (sLit "few") + | otherwise = ptext (sLit "many") + extra | n_fun == n_res = empty + | otherwise = ptext (sLit "Probable cause:") <+> quotes (ppr fun) + <+> ptext (sLit "is applied to too") <+> what + <+> ptext (sLit "arguments") + msg = ptext (sLit "In the return type of a call of") <+> quotes (ppr fun) + ; return (env0, msg $$ extra) } + badFieldTypes :: [(Name,TcType)] -> SDoc badFieldTypes prs = hang (ptext (sLit "Record update for insufficiently polymorphic field")