
#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 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: -------------------------------------+------------------------------------- The latest installment in "Ryan finds minor bugs in `-ddump-splices`". Take this program: {{{#!hs {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -ddump-splices #-} module Bug where $([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 |]) }}} Compiling this gives: {{{ $ /opt/ghc/8.2.2/bin/ghci Bug.hs GHCi, version 8.2.2: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:(6,3)-(15,6): Splicing declarations [d| f_a1sB :: Bool -> Bool f_a1sB x_a1sD = case x_a1sD of (True :: Bool) -> True (False :: Bool) -> False g_a1sC :: Bool -> Bool g_a1sC x_a1sE = (case x_a1sE of True -> True False -> False) :: Bool |] ======> f_a49Z :: Bool -> Bool f_a49Z x_a4a0 = case x_a4a0 of True :: Bool -> True False :: Bool -> False g_a49Y :: Bool -> Bool g_a49Y x_a4a1 = case x_a4a1 of True -> True False -> False :: Bool }}} Neither the `-ddump-splices` output for `f` nor `g` parse are legal Haskell: * In `f`, GHC fails to parenthesize the pattern signatures `True :: Bool` and `False :: Bool`. * In `g`, GHC fails to parenthesize the `case` expression which has an explicit `Bool` signature. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14875 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler