#5318: badly formatted error message
---------------------------------+------------------------------------------
Reporter: igloo | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
When compiling this module:
{{{
module Foo where
pprx
= text "aaaaaaaaaa"
$$ text "bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb"
$$ text ""
$$ text "ccccccccccccccccccccccccccccccccccccc"
$$ text ""
$$ text "ddddddddddddddddddddddddddddddddddddddddd"
$$ ppr (raCodeCoalesced s)
$$ text ""
$$ text ""
s = undefined
($$) = undefined
text = undefined
raCodeCoalesced = undefined
class Outputable a where
ppr :: a -> ()
}}}
GHC gives a poorly formatted error message:
{{{
$ ghc -c w.hs
w.hs:11:8:
Ambiguous type variable `a0' in the constraint:
(Outputable a0) arising from a use of `ppr'
Probable fix: add a type signature that fixes these type variable(s)
In the second argument of `($$)', namely `ppr (raCodeCoalesced s)'
In the first argument of `($$)', namely
`text "aaaaaaaaaa" $$ text "bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb"
$$
text ""
$$
text "ccccccccccccccccccccccccccccccccccccc"
$$
text ""
$$
text "ddddddddddddddddddddddddddddddddddddddddd"
$$
ppr (raCodeCoalesced s)'
In the first argument of `($$)', namely
`text "aaaaaaaaaa" $$ text "bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb"
$$
text ""
$$
text "ccccccccccccccccccccccccccccccccccccc"
$$
text ""
$$
text "ddddddddddddddddddddddddddddddddddddddddd"
$$
ppr (raCodeCoalesced s)
$$
text ""'
}}}
I would expect the entire quoted code to be indented at least 7 spaces.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5318>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs