[GHC] #15324: -ddump-splices does not parenthesize rank-n contexts correctly
GHC
ghc-devs at haskell.org
Fri Jun 29 20:04:31 UTC 2018
#15324: -ddump-splices does not parenthesize rank-n contexts correctly
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Template | Version: 8.4.3
Haskell |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Ryan discovers another `-ddump-splices` bug—news at 11:
{{{#!hs
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
$([d| f :: forall a. (Show a => a) -> a
f _ = undefined
|])
}}}
{{{
$ /opt/ghc/8.4.3/bin/ghci Bug.hs -dsuppress-uniques
GHCi, version 8.4.3: 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)-(8,6): Splicing declarations
[d| f :: forall a. (Show a => a) -> a
f _ = undefined |]
======>
f :: forall a. Show a => a -> a
f _ = undefined
}}}
Notice that `f`'s type signature is pretty-printed as `forall a. Show a =>
a -> a`, which is just wrong. Patch incoming.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15324>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list