[GHC] #11341: Reifying a GADT doesn't tell you the correct return type
GHC
ghc-devs at haskell.org
Sat Jan 2 23:01:23 UTC 2016
#11341: Reifying a GADT doesn't tell you the correct return type
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Template | Version: 8.1
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:
-------------------------------------+-------------------------------------
Running this example:
{{{#!hs
{-# LANGUAGE GADTs, TemplateHaskell #-}
module Main (main) where
import Language.Haskell.TH
type S = T
data T a where
MkT :: S Int
$(return [])
main :: IO ()
main = putStrLn $(reify ''T >>= stringE . pprint)
}}}
gives the following result:
{{{
data Main.T (a_0 :: *) where Main.MkT :: Main.T GHC.Types.Int
}}}
Shouldn't the return type be `Main.S GHC.Types.Int` instead?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11341>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list