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

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Template | Version: 8.0.1 Haskell | 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): | Wiki Page: -------------------------------------+------------------------------------- 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 #) |] ======> In }}} 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 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge 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: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: patch => merge * testcase: => th/T12513 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge 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: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Should we really merge this? Perhaps there's code that assumes the broken treatment that has existed for some time... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge 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: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Hm, that's a good point. I was mentally lumping this ticket in the same category as #12403, which I also marked as merge... perhaps that ought to be moved to the 8.2.1 release as well? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge 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: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Well, yes. They should both be merged or neither. I favor "neither"... unless it's important for your work that they be merged. As a heavy TH user, I've worked around a bunch of TH bugs to get th-desugar and singletons working, and a fix like this between major releases would cause me a headache. (Not in this particular case, though.) That said, perhaps no one other than you has hit these bugs, in which case it's safe to merge. I leave it to your judgment, based on how it would affect your work if these were not merged until 8.2. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12513: Template Haskell boxes singleton unboxed tuples when splicing them
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: merge
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: th/T12513
Blocked By: | Blocking:
Related Tickets: #5332 | Differential Rev(s): Phab:D2462
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: merge => closed * resolution: => fixed Comment: I don't have an overwhelmingly strong desire to use these changes in 8.0.2, so I'll be conservative and postpone this change until GHC 8.2.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12513: Template Haskell boxes singleton unboxed tuples when splicing them -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Template Haskell | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC accepts | Unknown/Multiple invalid program | Test Case: th/T12513 Blocked By: | Blocking: Related Tickets: #5332 | Differential Rev(s): Phab:D2462 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: 8.0.2 => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12513#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC