[GHC] #14681: More incorrect Template Haskell parenthesization
GHC
ghc-devs at haskell.org
Wed Jan 17 17:33:21 UTC 2018
#14681: More incorrect Template Haskell parenthesization
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.2.2
Haskell |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The latest installment of "RyanGlScott finds bugs in Template Haskell
pretty-printing". Here is what's featured on today's episode:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import Data.Functor.Identity
import Language.Haskell.TH
$([d| f = \(Identity x) -> x |])
$([d| g = $(pure $ VarE '(+) `AppE` LitE (IntegerL (-1)) `AppE` (LitE
(IntegerL (-1)))) |])
}}}
Running this with GHC 8.2 or later yields some incorrectly parenthesized
output:
{{{
$ /opt/ghc/8.2.2/bin/ghc Bug.hs
[1 of 1] Compiling Bug ( Bug.hs, Bug.o )
Bug.hs:8:3-31: Splicing declarations
[d| f_azO = \ (Identity x_azP) -> x_azP |]
======>
f_a3Nx = \ Identity x_a3Ny -> x_a3Ny
Bug.hs:9:3-90: Splicing declarations
[d| g_a3NU
= $(pure
$ VarE '(+) `AppE` LitE (IntegerL (- 1))
`AppE` (LitE (IntegerL (- 1)))) |]
pending(rn) [<splice_a3NV, pure
$ VarE '(+) `AppE` LitE (IntegerL (- 1))
`AppE` (LitE (IntegerL (- 1)))>]
======>
g_a4dU = ((+) -1) -1
}}}
In particular, look at these two lines:
{{{
f_a3Nx = \ Identity x_a3Ny -> x_a3Ny
g_a4dU = ((+) -1) -1
}}}
These should be:
{{{
f_a3Nx = \ (Identity x_a3Ny) -> x_a3Ny
g_a4dU = ((+) (-1)) (-1)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14681>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list