Skip to content

Mangled reified GADT record selector

From @RyanGlScott (originally #16980 (comment 222424), but unrelated to that ticket):

Consider this program:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where

import Language.Haskell.TH

$([d| data T b where
        MkT :: { unT :: a } -> T a
    |])

$(return [])

main :: IO ()
main = putStrLn $(reify 'unT >>= stringE . pprint)

If you run this, you'll get a surprising answer:

$ /opt/ghc/8.8.1/bin/runghc Bug.hs
Main.unT :: forall (a_0 :: *) . Main.T b_1 -> b_1

The reported type is forall a. T b -> b, which is completely bogus! Even stranger is that if I load this module into GHCi and then reify it:

$ /opt/ghc/8.8.1/bin/ghci Bug.hs -XTemplateHaskell
GHCi, version 8.8.1: https://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Main             ( Bug.hs, interpreted )
Ok, one module loaded.
λ> import Language.Haskell.TH
λ> putStrLn $(reify 'unT >>= stringE . pprint)
Main.unT :: forall (a_0 :: *) . Main.T a_0 -> a_0

Then the reported type is forall a. T a -> a, as expected. I can't help but wonder if this is another case of metavariables leaking through when they shouldn't.

To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information