-ddump-splices fails to preserve DataKinds tick when splicing InfixT
If you compile the following code:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import GHC.Generics
import Language.Haskell.TH
type T = $(infixT (promotedT 'Nothing) '(:*:) (promotedT 'Nothing))
You'll get the following -ddump-splices
output:
$ /opt/ghc/8.8.1/bin/ghci Bug.hs
GHCi, version 8.8.1: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:9:12-66: Splicing type
infixT (promotedT 'Nothing) '(:*:) (promotedT 'Nothing)
======>
(:*:) 'Nothing 'Nothing
Ok, one module loaded.
Notice how the type that gets spliced in is (:*:) 'Nothing 'Nothing
. This is actually incorrect, since I used (:*:)
as a data constructor name in the original code (i.e., '(:*:)
), not (:*:)
as a type constructor name (i.e., ''(:*:)
). One consequence is that copy-pasting (:*:) 'Nothing 'Nothing
back into a Haskell file will fail.
Patch incoming.