[GHC] #12513: Template Haskell boxes singleton unboxed tuples when splicing them

GHC ghc-devs at haskell.org
Mon Aug 22 00:22:17 UTC 2016


#12513: Template Haskell boxes singleton unboxed tuples when splicing them
-------------------------------------+-------------------------------------
        Reporter:  RyanGlScott       |                Owner:
            Type:  bug               |               Status:  patch
        Priority:  normal            |            Milestone:  8.0.2
       Component:  Template Haskell  |              Version:  8.0.1
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  GHC accepts       |  Unknown/Multiple
  invalid program                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #5332             |  Differential Rev(s):  Phab:D2462
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * status:  new => patch
 * differential:   => Phab:D2462
 * milestone:   => 8.0.2


@@ -29,1 +29,1 @@
- Bug.hs:9:8-23: Splicing type [t| (# Int #) |] ======> In
+ Bug.hs:9:8-23: Splicing type [t| (# Int #) |] ======> Int

New description:

 As noticed [https://phabricator.haskell.org/D2448#71603 here], this
 program somehow compiles:

 {{{#!hs
 {-# LANGUAGE TemplateHaskell #-}
 {-# LANGUAGE UnboxedTuples #-}
 module Bug where

 import Language.Haskell.TH.Lib
 import Language.Haskell.TH.Ppr
 import Language.Haskell.TH.Syntax

 f :: $([t| (# Int #) |]) -> Int
 f x = x

 g :: $(unboxedTupleT 1 `appT` conT ''Int) -> Int
 g x = x
 }}}

 Despite the fact that `(# Int #)` and `Int` are most definitely //not//
 the same type! If you compile with `-ddump-splices`, you'll see what's
 going on:

 {{{
 $ /opt/ghc/head/bin/ghc Bug.hs -ddump-splices
 [1 of 1] Compiling Bug              ( Bug.hs, Bug.o )
 Bug.hs:12:8-40: Splicing type
     unboxedTupleT 1 `appT` conT ''Int ======> Int
 Bug.hs:9:8-23: Splicing type [t| (# Int #) |] ======> Int
 }}}

 It appears that the splicing machinery is turning `(# Int #)` into `Int`
 behind the scenes. Luckily, this should be easy to fix. Patch coming soon.

--

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12513#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list