[commit: ghc] master: Fix #15073 by suggesting UnboxedTuples in an error message (0c7db22)

git at git.haskell.org git at git.haskell.org
Wed May 16 19:41:08 UTC 2018


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

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

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

commit 0c7db226012b5cfafc9a38bfe372661672ec8900
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Wed May 16 12:59:45 2018 -0400

    Fix #15073 by suggesting UnboxedTuples in an error message
    
    Under certain circumstances, `GeneralizedNewtypeDeriving`
    can emit code which uses unboxed tuple types, but if `UnboxedTuples`
    wasn't enabled, the error message that GHC gave didn't make it very
    clear that it could be worked around by explicitly enabling the
    extension. Easily fixed.
    
    Test Plan: make test TEST=T15073
    
    Reviewers: bgamari
    
    Reviewed By: bgamari
    
    Subscribers: simonpj, thomie, carter
    
    GHC Trac Issues: #15073
    
    Differential Revision: https://phabricator.haskell.org/D4620


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

0c7db226012b5cfafc9a38bfe372661672ec8900
 compiler/typecheck/TcValidity.hs                   |  5 ++++-
 testsuite/tests/deriving/should_fail/T15073.hs     |  8 ++++++++
 testsuite/tests/deriving/should_fail/T15073.stderr | 22 ++++++++++++++++++++++
 testsuite/tests/deriving/should_fail/T15073a.hs    |  5 +++++
 testsuite/tests/deriving/should_fail/all.T         |  2 ++
 5 files changed, 41 insertions(+), 1 deletion(-)

diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index 617975e..bdda6cd 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -621,7 +621,10 @@ forAllEscapeErr env ty tau_kind
                  , text "of kind:" <+> ppr_tidy env tau_kind ]) )
 
 ubxArgTyErr :: TidyEnv -> Type -> (TidyEnv, SDoc)
-ubxArgTyErr env ty = (env, sep [text "Illegal unboxed tuple type as function argument:", ppr_tidy env ty])
+ubxArgTyErr env ty
+  = ( env, vcat [ sep [ text "Illegal unboxed tuple type as function argument:"
+                      , ppr_tidy env ty ]
+                , text "Perhaps you intended to use UnboxedTuples" ] )
 
 {-
 Note [Liberal type synonyms]
diff --git a/testsuite/tests/deriving/should_fail/T15073.hs b/testsuite/tests/deriving/should_fail/T15073.hs
new file mode 100644
index 0000000..ecceeed
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T15073.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE TypeInType #-}
+module T15073 where
+
+import T15073a
+
+newtype Foo a = MkFoo a
+  deriving P
diff --git a/testsuite/tests/deriving/should_fail/T15073.stderr b/testsuite/tests/deriving/should_fail/T15073.stderr
new file mode 100644
index 0000000..7658b8e
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T15073.stderr
@@ -0,0 +1,22 @@
+
+T15073.hs:8:12: error:
+    • Illegal unboxed tuple type as function argument: (# a #)
+      Perhaps you intended to use UnboxedTuples
+    • In the expression:
+        GHC.Prim.coerce
+          @(a
+            -> (Unit# a :: TYPE (GHC.Types.TupleRep ((:) GHC.Types.LiftedRep ([] :: [] GHC.Types.RuntimeRep) :: [] GHC.Types.RuntimeRep))))
+          @(Foo a
+            -> (Unit# (Foo a) :: TYPE (GHC.Types.TupleRep ((:) GHC.Types.LiftedRep ([] :: [] GHC.Types.RuntimeRep) :: [] GHC.Types.RuntimeRep))))
+          p
+      In an equation for ‘p’:
+          p = GHC.Prim.coerce
+                @(a
+                  -> (Unit# a :: TYPE (GHC.Types.TupleRep ((:) GHC.Types.LiftedRep ([] :: [] GHC.Types.RuntimeRep) :: [] GHC.Types.RuntimeRep))))
+                @(Foo a
+                  -> (Unit# (Foo a) :: TYPE (GHC.Types.TupleRep ((:) GHC.Types.LiftedRep ([] :: [] GHC.Types.RuntimeRep) :: [] GHC.Types.RuntimeRep))))
+                p
+      When typechecking the code for ‘p’
+        in a derived instance for ‘P (Foo a)’:
+        To see the code I am typechecking, use -ddump-deriv
+      In the instance declaration for ‘P (Foo a)’
diff --git a/testsuite/tests/deriving/should_fail/T15073a.hs b/testsuite/tests/deriving/should_fail/T15073a.hs
new file mode 100644
index 0000000..87e7571
--- /dev/null
+++ b/testsuite/tests/deriving/should_fail/T15073a.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE UnboxedTuples #-}
+module T15073a where
+
+class P a where
+  p :: a -> (# a #)
diff --git a/testsuite/tests/deriving/should_fail/all.T b/testsuite/tests/deriving/should_fail/all.T
index 8dc5b78..f1d8261 100644
--- a/testsuite/tests/deriving/should_fail/all.T
+++ b/testsuite/tests/deriving/should_fail/all.T
@@ -72,3 +72,5 @@ test('T14365', [extra_files(['T14365B.hs','T14365B.hs-boot'])],
 test('T14728a', normal, compile_fail, [''])
 test('T14728b', normal, compile_fail, [''])
 test('T14916', normal, compile_fail, [''])
+test('T15073', [extra_files(['T15073a.hs'])], multimod_compile_fail,
+               ['T15073', '-v0'])



More information about the ghc-commits mailing list