diff --git a/ghc/compiler/typecheck/TcBinds.lhs b/ghc/compiler/typecheck/TcBinds.lhs
index a7a589c7125f3fd5c81024f7b5d747e155bbe0fd..1a360513e8e16a80cb391a6552409eafccfd2e0e 100644
--- a/ghc/compiler/typecheck/TcBinds.lhs
+++ b/ghc/compiler/typecheck/TcBinds.lhs
@@ -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
diff --git a/ghc/compiler/typecheck/TcMonoType.lhs b/ghc/compiler/typecheck/TcMonoType.lhs
index 0943cfb792e9b680126ba11e1eaacce63868249e..2745f78a6c19a40a3e1dd899591286f8ab244cd6 100644
--- a/ghc/compiler/typecheck/TcMonoType.lhs
+++ b/ghc/compiler/typecheck/TcMonoType.lhs
@@ -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
 		   ]
diff --git a/ghc/compiler/utils/Outputable.lhs b/ghc/compiler/utils/Outputable.lhs
index 1f23e5e853ed6eee0af87c949ec15ac468970fbb..19ad6666776d7e8c70529c129e9f229dc1e72a15 100644
--- a/ghc/compiler/utils/Outputable.lhs
+++ b/ghc/compiler/utils/Outputable.lhs
@@ -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)