[GHC] #7645: Parens in an error message

#7645: Parens in an error message -----------------------------+---------------------------------------------- Reporter: monoidal | Owner: Type: bug | Status: new Priority: normal | Component: Compiler Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: #7609 -----------------------------+---------------------------------------------- {{{ {-# LANGUAGE TypeOperators #-} data (+) a b f :: ((+) a a, Maybe) f = undefined }}} gives {{{ X.hs:3:16: Expecting one more argument to `Maybe' In the type signature for `f': f :: (+ a a, Maybe) }}} which should be `(+) a a`. I tried {{{ #!diff diff --git a/compiler/hsSyn/HsTypes.lhs b/compiler/hsSyn/HsTypes.lhs index 74aa477..d0d9e1a 100644 --- a/compiler/hsSyn/HsTypes.lhs +++ b/compiler/hsSyn/HsTypes.lhs @@ -614,7 +614,7 @@ ppr_mono_ty ctxt_prec (HsForAllTy exp tvs ctxt ty) ppr_mono_ty _ (HsBangTy b ty) = ppr b <> ppr_mono_lty pREC_CON ty ppr_mono_ty _ (HsQuasiQuoteTy qq) = ppr qq ppr_mono_ty _ (HsRecTy flds) = pprConDeclFields flds -ppr_mono_ty _ (HsTyVar name) = ppr name +ppr_mono_ty _ (HsTyVar name) = pprPrefixOcc name ppr_mono_ty prec (HsFunTy ty1 ty2) = ppr_fun_ty prec ty1 ty2 ppr_mono_ty _ (HsTupleTy con tys) = tupleParens std_con (interpp'SP tys) where std_con = case con of }}} but this causes the kind * to be printed as (*). -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7645 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7645: Parens in an error message
-----------------------------+----------------------------------------------
Reporter: monoidal | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.6.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: None/Unknown | Blockedby:
Blocking: | Related: #7609
-----------------------------+----------------------------------------------
Comment(by simonpj@…):
commit 599aaf4e4dbb94a484eed5f624404194c6ca1fb9
{{{
Author: Simon Peyton Jones

#7645: Parens in an error message ------------------------------------------+--------------------------------- Reporter: monoidal | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Resolution: fixed | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: typecheck/should_fail/T7645 | Blockedby: Blocking: | Related: #7609 ------------------------------------------+--------------------------------- Changes (by simonpj): * status: new => closed * difficulty: => Unknown * resolution: => fixed * testcase: => typecheck/should_fail/T7645 Comment: Thanks! Fixed. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7645#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC