[commit: ghc] ghc-8.0: Fix Template Haskell reification of unboxed tuple types (3470f82)

git at git.haskell.org git at git.haskell.org
Thu Aug 25 15:04:55 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/3470f82fbd7039f9957761c5a12988fd558d6cb8/ghc

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

commit 3470f82fbd7039f9957761c5a12988fd558d6cb8
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Mon Jul 18 09:29:05 2016 -0400

    Fix Template Haskell reification of unboxed tuple types
    
    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
    
    (cherry picked from commit 514c4a4741f3881672f1ccc1fe6d08a5d596bb87)


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

3470f82fbd7039f9957761c5a12988fd558d6cb8
 compiler/typecheck/TcSplice.hs                     |  4 +-
 docs/users_guide/8.0.2-notes.rst                   | 59 ++++++++++++++++++++++
 .../tests/th/{T10697_decided_1.hs => T12403.hs}    |  5 +-
 testsuite/tests/th/T12403.stdout                   |  1 +
 testsuite/tests/th/all.T                           |  2 +
 5 files changed, 68 insertions(+), 3 deletions(-)

diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs
index 82853e1..06b4932 100644
--- a/compiler/typecheck/TcSplice.hs
+++ b/compiler/typecheck/TcSplice.hs
@@ -1733,7 +1733,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
diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst
new file mode 100644
index 0000000..39ad028
--- /dev/null
+++ b/docs/users_guide/8.0.2-notes.rst
@@ -0,0 +1,59 @@
+.. _release-8-0-2:
+
+Release notes for version 8.0.2
+===============================
+
+TODO FIXME
+
+Highlights
+----------
+
+TODO FIXME.
+
+Full details
+------------
+
+Language
+~~~~~~~~
+
+-  TODO FIXME.
+
+-  :ghc-flag:`-XStaticPointers` now allows the body of the ``static`` form to
+   refer to closed local bindings. For instance, this is now permitted:
+   ``f = static x where x = 'a'``.
+
+Compiler
+~~~~~~~~
+
+-  TODO FIXME.
+
+-  The :ghc-flag:`-ddump-cmm` now dumps the result after C-- pipeline pass. Two
+   more flags were added: :ghc-flag:`-ddump-cmm-from-stg` to allow to get the
+   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
+~~~~~~~~~~~~~~~~~~~~~~~~
+
+-  GHCi now supports two new commands. :ghci-cmd:`:type` ``+d`` performs
+   defaulting on the type before reporting it to the user, and
+   :ghci-cmd:`:type` ``+v`` refrains from instantiating any variables before
+   reporting, which is useful in concert with :ghc-flag:`-XTypeApplications`.
+
+   .. code-block:: none
+
+	*X> :type +d length
+	length :: [a] -> Int
+
+	*X> :set -fprint-explicit-foralls
+	*X> :type length
+	length :: forall {a} {t :: * -> *}. Foldable t => t a -> Int
+	*X> :type +v length
+	length :: forall (t :: * -> *). Foldable t => forall a. t a -> Int
diff --git a/testsuite/tests/th/T10697_decided_1.hs b/testsuite/tests/th/T12403.hs
similarity index 50%
copy from testsuite/tests/th/T10697_decided_1.hs
copy to testsuite/tests/th/T12403.hs
index 241cec3..d4aad62 100644
--- a/testsuite/tests/th/T10697_decided_1.hs
+++ b/testsuite/tests/th/T12403.hs
@@ -1,11 +1,12 @@
 {-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnboxedTuples #-}
 module Main where
 
 import Language.Haskell.TH
 
-data T = T {-# UNPACK #-} !Int !Int Int
+data T = T (# Int, Int #)
 
 $(return [])
 
 main :: IO ()
-main = putStrLn $(reifyConStrictness 'T >>= stringE . show)
+main = putStrLn $(reify ''T >>= stringE . pprint)
diff --git a/testsuite/tests/th/T12403.stdout b/testsuite/tests/th/T12403.stdout
new file mode 100644
index 0000000..9b75e8b
--- /dev/null
+++ b/testsuite/tests/th/T12403.stdout
@@ -0,0 +1 @@
+data Main.T = Main.T ((# , #) GHC.Types.Int GHC.Types.Int)
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index f502252..5180edd 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -411,3 +411,5 @@ test('T11941', normal, compile_fail, ['-v0'])
 test('T11484', normal, compile, ['-v0'])
 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'])



More information about the ghc-commits mailing list