Skip to content
Snippets Groups Projects
Commit 6f531423 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

[project @ 2000-04-03 16:46:41 by simonpj]

* Minor wibble to type checker error message

* Make error messages come out to stderr (I'd switched
  to stdout temporarily when fighting the Dreaded Stderr Bug
  and forgot to change back)
parent b5bafea8
No related merge requests found
......@@ -796,7 +796,7 @@ checkSigMatch top_lvl binder_names mono_ids sigs
mk_dict_tys theta = map mkPredTy theta
sig_msg id = ptext SLIT("When checking the type signature for") <+> ppr id
sig_msg id = ptext SLIT("When checking the type signature for") <+> quotes (ppr id)
-- Search for Main.main in the binder_names, return corresponding mono_id
find_main NotTopLevel binder_names mono_ids = Nothing
......
......@@ -38,7 +38,7 @@ import Type ( Type, PredType(..), ThetaType, UsageAnn(..),
boxedTypeKind, unboxedTypeKind, tyVarsOfType,
mkArrowKinds, getTyVar_maybe, getTyVar,
tidyOpenType, tidyOpenTypes, tidyTyVar, tidyTyVars,
tyVarsOfType, tyVarsOfTypes
tyVarsOfType, tyVarsOfTypes, mkForAllTys
)
import PprType ( pprConstraint, pprType )
import Subst ( mkTopTyVarSubst, substTy )
......@@ -688,9 +688,7 @@ sigCtxt when sig_tyvars sig_theta sig_tau tidy_env
(env1, tidy_sig_tyvars) = tidyTyVars tidy_env sig_tyvars
(env2, tidy_sig_rho) = tidyOpenType env1 (mkRhoTy sig_theta sig_tau)
(env3, tidy_actual_tau) = tidyOpenType env1 actual_tau
forall | null sig_tyvars = empty
| otherwise = ptext SLIT("forall") <+> hsep (map ppr tidy_sig_tyvars) <> dot
msg = vcat [ptext SLIT("Signature type: ") <+> forall <+> pprType tidy_sig_rho,
msg = vcat [ptext SLIT("Signature type: ") <+> pprType (mkForAllTys tidy_sig_tyvars tidy_sig_rho),
ptext SLIT("Type to generalise:") <+> pprType tidy_actual_tau,
when
]
......
......@@ -155,7 +155,7 @@ printSDoc d sty = printDoc PageMode stdout (d sty)
-- I'm not sure whether the direct-IO approach of printDoc
-- above is better or worse than the put-big-string approach here
printErrs :: SDoc -> IO ()
printErrs doc = printDoc PageMode stdout (final_doc user_style)
printErrs doc = printDoc PageMode stderr (final_doc user_style)
where
final_doc = doc -- $$ text ""
user_style = mkUserStyle (PartWay opt_PprUserLength)
......
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