[commit: ghc] master: Splice singleton unboxed tuples correctly with Template Haskell (fb0d87f)

git at git.haskell.org git at git.haskell.org
Mon Aug 22 14:40:48 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/fb0d87f1c4a35fa2aaf7f6dd55edbc71c7c3b44d/ghc

>---------------------------------------------------------------

commit fb0d87f1c4a35fa2aaf7f6dd55edbc71c7c3b44d
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Mon Aug 22 10:39:12 2016 -0400

    Splice singleton unboxed tuples correctly with Template Haskell
    
    Summary:
    Previously, TH would implicitly remove the parentheses when splicing in
    singleton unboxed tuple types (e.g., turning `(# Int #)` into `Int`). Luckily,
    the fix is simply to delete some code.
    
    Fixes #12513.
    
    Test Plan: make test TEST=T12513
    
    Reviewers: hvr, bgamari, austin, goldfire
    
    Reviewed By: goldfire
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2462
    
    GHC Trac Issues: #12513


>---------------------------------------------------------------

fb0d87f1c4a35fa2aaf7f6dd55edbc71c7c3b44d
 compiler/hsSyn/Convert.hs        |  4 +---
 docs/users_guide/8.0.2-notes.rst |  4 ++++
 testsuite/tests/th/T12513.hs     | 12 ++++++++++++
 testsuite/tests/th/T12513.stderr | 10 ++++++++++
 testsuite/tests/th/all.T         |  1 +
 5 files changed, 28 insertions(+), 3 deletions(-)

diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index ad51f9d..ee1f106 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -1134,9 +1134,7 @@ cvtTypeKind ty_str ty
              -> mk_apps (HsTyVar (noLoc (getRdrName (tupleTyCon Boxed n)))) tys'
            UnboxedTupleT n
              | length tys' == n         -- Saturated
-             -> if n==1 then return (head tys') -- Singleton tuples treated
-                                                -- like nothing (ie just parens)
-                        else returnL (HsTupleTy HsUnboxedTuple tys')
+             -> returnL (HsTupleTy HsUnboxedTuple tys')
              | otherwise
              -> mk_apps (HsTyVar (noLoc (getRdrName (tupleTyCon Unboxed n))))
                         tys'
diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst
index 39ad028..f75c684 100644
--- a/docs/users_guide/8.0.2-notes.rst
+++ b/docs/users_guide/8.0.2-notes.rst
@@ -39,6 +39,10 @@ Template Haskell
    Template Haskell reified unboxed tuples as boxed tuples with twice their
    appropriate arity.)
 
+-  Splicing singleton unboxed tuple types (e.g., ``(# Int #)``) now works
+   correctly. Previously, Template Haskell would implicitly remove the
+   parentheses when splicing, which would turn ``(# Int #)`` into ``Int``.
+
 TODO FIXME Heading title
 ~~~~~~~~~~~~~~~~~~~~~~~~
 
diff --git a/testsuite/tests/th/T12513.hs b/testsuite/tests/th/T12513.hs
new file mode 100644
index 0000000..625e4c4
--- /dev/null
+++ b/testsuite/tests/th/T12513.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnboxedTuples #-}
+module T12513 where
+
+import Language.Haskell.TH.Lib
+import Language.Haskell.TH.Syntax
+
+f :: $([t| (# Int #) |]) -> Int
+f x = x
+
+g :: $(unboxedTupleT 1 `appT` conT ''Int) -> Int
+g x = x
diff --git a/testsuite/tests/th/T12513.stderr b/testsuite/tests/th/T12513.stderr
new file mode 100644
index 0000000..26a2dbb
--- /dev/null
+++ b/testsuite/tests/th/T12513.stderr
@@ -0,0 +1,10 @@
+
+T12513.hs:9:7: error:
+    • Couldn't match expected type ‘Int’ with actual type ‘(# Int #)’
+    • In the expression: x
+      In an equation for ‘f’: f x = x
+
+T12513.hs:12:7: error:
+    • Couldn't match expected type ‘Int’ with actual type ‘(# Int #)’
+    • In the expression: x
+      In an equation for ‘g’: g x = x
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index 5cece92..b05d601 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -421,3 +421,4 @@ test('T12130', extra_clean(['T12130a.hi','T12130a.o']),
 test('T12403', omit_ways(['ghci']),
               compile_and_run, ['-v0 -ddump-splices -dsuppress-uniques'])
 test('T12407', omit_ways(['ghci']), compile, ['-v0'])
+test('T12513', omit_ways(['ghci']), compile_fail, ['-v0'])



More information about the ghc-commits mailing list