Skip to content

Commit

Permalink
Fix Template Haskell reification of unboxed tuple types
Browse files Browse the repository at this point in the history
Summary:
Previously, Template Haskell reified unboxed tuple types as boxed
tuples with twice the appropriate arity.

Fixes #12403.

Test Plan: make test TEST=T12403

Reviewers: hvr, goldfire, austin, bgamari

Reviewed By: goldfire

Subscribers: thomie

Differential Revision: https://phabricator.haskell.org/D2405

GHC Trac Issues: #12403
  • Loading branch information
RyanGlScott committed Jul 18, 2016
1 parent 3fa3fe8 commit 514c4a4
Show file tree
Hide file tree
Showing 5 changed files with 24 additions and 1 deletion.
4 changes: 3 additions & 1 deletion compiler/typecheck/TcSplice.hs
Expand Up @@ -1819,7 +1819,9 @@ reify_tc_app tc tys
tc_binders = tyConBinders tc
tc_res_kind = tyConResKind tc

r_tc | isTupleTyCon tc = if isPromotedDataCon tc
r_tc | isUnboxedTupleTyCon tc = TH.UnboxedTupleT (arity `div` 2)
-- See Note [Unboxed tuple RuntimeRep vars] in TyCon
| isTupleTyCon tc = if isPromotedDataCon tc
then TH.PromotedTupleT arity
else TH.TupleT arity
| tc `hasKey` listTyConKey = TH.ListT
Expand Down
6 changes: 6 additions & 0 deletions docs/users_guide/8.0.2-notes.rst
Expand Up @@ -32,6 +32,12 @@ Compiler
initial cmm from STG-to-C-- code generation and :ghc-flag:`-ddump-cmm-verbose`
to obtain the intermediates from all C-- pipeline stages.

Template Haskell
~~~~~~~~~~~~~~~~

- Reifying types that contain unboxed tuples now works correctly. (Previously,
Template Haskell reified unboxed tuples as boxed tuples with twice their
appropriate arity.)

TODO FIXME Heading title
~~~~~~~~~~~~~~~~~~~~~~~~
Expand Down
12 changes: 12 additions & 0 deletions testsuite/tests/th/T12403.hs
@@ -0,0 +1,12 @@
{-# 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)
1 change: 1 addition & 0 deletions testsuite/tests/th/T12403.stdout
@@ -0,0 +1 @@
data Main.T = Main.T ((# , #) GHC.Types.Int GHC.Types.Int)
2 changes: 2 additions & 0 deletions testsuite/tests/th/all.T
Expand Up @@ -418,3 +418,5 @@ test('T11484', normal, compile, ['-v0'])
test('T8761', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T12130', extra_clean(['T12130a.hi','T12130a.o']),
multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags])
test('T12403', omit_ways(['ghci']),
compile_and_run, ['-v0 -ddump-splices -dsuppress-uniques'])

0 comments on commit 514c4a4

Please sign in to comment.