[GHC] #12403: Template Haskell boxes tuple types when reifying them
GHC
ghc-devs at haskell.org
Sat Jul 16 23:28:29 UTC 2016
#12403: Template Haskell boxes tuple types when reifying them
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone: 8.0.2
Component: Template | Version: 8.0.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:
-------------------------------------+-------------------------------------
Example:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UnboxedTuples #-}
module Main where
import Language.Haskell.TH
data T = T (# Int, Int #)
$(return [])
main :: IO ()
main = putStrLn $(reify ''T >>= stringE . pprint)
}}}
{{{
$ /opt/ghc/8.0.1/bin/ghc -fforce-recomp Constraints.hs
[1 of 1] Compiling Main ( Constraints.hs, Constraints.o )
Linking Constraints ...
$ ./Constraints
data Main.T = Main.T ((,,,) GHC.Types.Int GHC.Types.Int)
}}}
Patch coming soon.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12403>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list