[GHC] #15572: TH improperly converts promoted data cons in ConT
GHC
ghc-devs at haskell.org
Mon Aug 27 18:27:45 UTC 2018
#15572: TH improperly converts promoted data cons in ConT
-------------------------------------+-------------------------------------
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:
-------------------------------------+-------------------------------------
If you compile the following program:
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import Language.Haskell.TH
$([d| type AbsoluteUnit1 = '() |])
$(pure [TySynD (mkName "AbsoluteUnit2") [] (ConT '())])
}}}
{{{
$ /opt/ghc/8.6.1/bin/ghci Bug.hs
GHCi, version 8.6.0.20180810: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:8:3-33: Splicing declarations
[d| type AbsoluteUnit1_a1HN = '() |]
======>
type AbsoluteUnit1_a4qs = '()
Bug.hs:9:3-54: Splicing declarations
pure [TySynD (mkName "AbsoluteUnit2") [] (ConT '())]
======>
type AbsoluteUnit2 = ()
}}}
You'll notice an unusual discrepancy between the two `-ddump-splices`
logs. In the first one:
{{{#!hs
type AbsoluteUnit1_a4qs = '()
}}}
The `'()` constructor is properly preceded with a single quote. In the
second one, however:
{{{#!hs
type AbsoluteUnit2 = ()
}}}
`'()` incorrectly appears without a single quote! The culprit is in the
way `Convert`
[http://git.haskell.org/ghc.git/blob/154d4e219cc0cebbef8a845609bd63ec45fdbea6:/compiler/hsSyn/Convert.hs#l1307
handles] `ConT`:
{{{#!hs
ConT nm -> do { nm' <- tconName nm
; mk_apps (HsTyVar noExt NotPromoted (noLoc nm'))
tys'}
}}}
This code naïvely assumes that `ConT` will never contain a promoted data
constructor name by hardcoding `NotPromoted`. We really ought to be
checking if `nm'` is a data con `RdrName` here and using `Promoted` if so,
and `NotPromoted` otherwise.
Patch incoming.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15572>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list