[commit: ghc] ghc-8.0: Revert "Fix Template Haskell reification of unboxed tuple types" (3219220)

git at git.haskell.org git at git.haskell.org
Thu Aug 25 15:10:26 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/3219220db283aa09396fc5fd7fe1668ecbe7a512/ghc

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

commit 3219220db283aa09396fc5fd7fe1668ecbe7a512
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Thu Aug 25 11:09:31 2016 -0400

    Revert "Fix Template Haskell reification of unboxed tuple types"
    
    This reverts commit 3470f82fbd7039f9957761c5a12988fd558d6cb8 which we
    decided not to merge afterall. See #12403.


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

3219220db283aa09396fc5fd7fe1668ecbe7a512
 compiler/typecheck/TcSplice.hs   |  4 +--
 docs/users_guide/8.0.2-notes.rst | 59 ----------------------------------------
 testsuite/tests/th/T12403.hs     | 12 --------
 testsuite/tests/th/T12403.stdout |  1 -
 testsuite/tests/th/all.T         |  2 --
 5 files changed, 1 insertion(+), 77 deletions(-)

diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs
index 06b4932..82853e1 100644
--- a/compiler/typecheck/TcSplice.hs
+++ b/compiler/typecheck/TcSplice.hs
@@ -1733,9 +1733,7 @@ reify_tc_app tc tys
     tc_binders  = tyConBinders tc
     tc_res_kind = tyConResKind tc
 
-    r_tc | isUnboxedTupleTyCon tc         = TH.UnboxedTupleT (arity `div` 2)
-             -- See Note [Unboxed tuple RuntimeRep vars] in TyCon
-         | isTupleTyCon tc                = if isPromotedDataCon tc
+    r_tc | 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
deleted file mode 100644
index 39ad028..0000000
--- a/docs/users_guide/8.0.2-notes.rst
+++ /dev/null
@@ -1,59 +0,0 @@
-.. _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/T12403.hs b/testsuite/tests/th/T12403.hs
deleted file mode 100644
index d4aad62..0000000
--- a/testsuite/tests/th/T12403.hs
+++ /dev/null
@@ -1,12 +0,0 @@
-{-# 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)
diff --git a/testsuite/tests/th/T12403.stdout b/testsuite/tests/th/T12403.stdout
deleted file mode 100644
index 9b75e8b..0000000
--- a/testsuite/tests/th/T12403.stdout
+++ /dev/null
@@ -1 +0,0 @@
-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 5180edd..f502252 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -411,5 +411,3 @@ 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