[GHC] #14875: -ddump-splices pretty-printing oddities with case statements
GHC
ghc-devs at haskell.org
Sat Apr 7 17:29:09 UTC 2018
#14875: -ddump-splices pretty-printing oddities with case statements
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Debugging | Unknown/Multiple
information is incorrect | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
I talked with alanz about this, and unfortunately, this isn't quite as
straightforward to fix as with previous pretty-priner bugs. This is that
we need to teach `cvtl` to put parentheses around expressions when
converting `SigE`s. At the same time, we don't want to add //unnecessary//
parentheses—we wouldn't want to convert `Just True :: Maybe Bool` to
`(Just True) :: Maybe Bool`, for instance.
Unfortunately, the machinery in GHC just isn't quite up to the task.
Currently, we have the
[http://git.haskell.org/ghc.git/blob/5819ae2173d4b16f1fde067d39c3c215a6adfe97:/compiler/hsSyn/HsExpr.hs#l1116
hsExprNeedsParens function], but this seems to assume that the argument
`HsExpr` is occurring in a function application context. In this scenario,
however, that's not the case: we have a `case` expression appearing in a
type annotation context. Alas, `hsExprNeedsParens` cannot distinguish
between the two contexts.
I think the right path forward here is to introduce a new precedence
argument to `hsExprNeedsParens`. Something like:
{{{#!hs
data Prec
= TopPrec -- Top-level
| SigPrec -- Argument of a type annotation (_ :: Foo)
| OpPrec -- Argument of an infix operator (_ + 1)
| AppPrec -- Argument of a prefix function (f _)
}}}
And use that to inform `hsExprNeedsParen` in the relevant cases. It's
worth noting that this data type is tantalizingly close the existing
[http://git.haskell.org/ghc.git/blob/5819ae2173d4b16f1fde067d39c3c215a6adfe97:/compiler/basicTypes/BasicTypes.hs#l700
TyPrec] data type:
{{{#!hs
data TyPrec
= TopPrec -- No parens
| FunPrec -- Function args; no parens for tycon apps
| TyOpPrec -- Infix operator
| TyConPrec -- Tycon args; no parens for atomic
}}}
Save for the fact that `TyPrec` currently doesn't have a `SigPrec`
constructor, and `TyPrec` has this funny business with `FunPrec`. It might
be worth considering if my proposed `Prec` and `TyPrec` could be merged.
Alas, I've run out of time, so this won't be happening today.
One last note: it turns out there's similar problems in the Template
Haskell pretty-printer as well:
{{{#!hs
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Bug2 where
import Language.Haskell.TH
main :: IO ()
main = putStrLn
$([d| f :: Bool -> Bool
f x = case x of
(True :: Bool) -> True
(False :: Bool) -> False
g :: Bool -> Bool
g x = (case x of
True -> True
False -> False) :: Bool
|] >>= stringE . pprint)
}}}
{{{
f_0 :: GHC.Types.Bool -> GHC.Types.Bool
f_0 x_1 = case x_1 of
GHC.Types.True :: GHC.Types.Bool -> GHC.Types.True
GHC.Types.False :: GHC.Types.Bool -> GHC.Types.False
g_2 :: GHC.Types.Bool -> GHC.Types.Bool
g_2 x_3 = case x_3 of
GHC.Types.True -> GHC.Types.True
GHC.Types.False -> GHC.Types.False :: GHC.Types.Bool
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14875#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list