[commit: ghc] ghc-8.0: Print foralls in user format (906ea04)

git at git.haskell.org git at git.haskell.org
Sun Oct 2 01:42:11 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/906ea0445deab65f4dfcba7473593db048cbacab/ghc

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

commit 906ea0445deab65f4dfcba7473593db048cbacab
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Sep 26 08:37:47 2016 +0100

    Print foralls in user format
    
    This fixes Trac #12597: in RnNames.warnMissingSignatures,
    use pprSigmaType not pprType
    
    (cherry picked from commit 796f0f2ad7eefd1c9af5a7ef9bf56848067e85b1)


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

906ea0445deab65f4dfcba7473593db048cbacab
 compiler/rename/RnNames.hs                                | 2 +-
 compiler/types/TyCoRep.hs                                 | 2 ++
 testsuite/tests/driver/werror.stderr                      | 3 +--
 testsuite/tests/indexed-types/should_compile/T8889.stderr | 4 +---
 testsuite/tests/parser/should_compile/read014.stderr      | 2 +-
 testsuite/tests/rename/should_compile/T12597.hs           | 5 +++++
 testsuite/tests/rename/should_compile/T12597.stderr       | 3 +++
 testsuite/tests/rename/should_compile/all.T               | 1 +
 testsuite/tests/typecheck/should_compile/T10971a.stderr   | 6 +++---
 testsuite/tests/typecheck/should_compile/tc243.stderr     | 2 +-
 testsuite/tests/warnings/should_compile/T11077.stderr     | 2 +-
 11 files changed, 20 insertions(+), 12 deletions(-)

diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 4c2d4f1..6ab51d9 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1617,7 +1617,7 @@ warnMissingSignatures gbl_env
                     = do { env <- tcInitTidyEnv     -- Why not use emptyTidyEnv?
                          ; let name    = idName id
                                (_, ty) = tidyOpenType env (idType id)
-                               ty_msg  = ppr ty
+                               ty_msg  = pprSigmaType ty
                          ; add_warn name $
                            hang (text "Top-level binding with no type signature:")
                               2 (pprPrefixName name <+> dcolon <+> ty_msg) }
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 7743a91..fc2ac90 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -2652,6 +2652,8 @@ ppr_fun_tail (ForAllTy (Anon ty1) ty2)
 ppr_fun_tail other_ty = [ppr_type TopPrec other_ty]
 
 pprSigmaType :: Type -> SDoc
+-- Prints a top-level type for the user; in particular
+-- top-level foralls are omitted unless you use -fprint-explicit-foralls
 pprSigmaType ty = sdocWithDynFlags $ \dflags ->
     eliminateRuntimeRep (ppr_sigma_type dflags False) ty
 
diff --git a/testsuite/tests/driver/werror.stderr b/testsuite/tests/driver/werror.stderr
index 8f2e603..436c980 100644
--- a/testsuite/tests/driver/werror.stderr
+++ b/testsuite/tests/driver/werror.stderr
@@ -17,8 +17,7 @@ werror.hs:10:1: warning: [-Wunused-top-binds (in -Wextra, -Wunused-binds)]
     Defined but not used: ‘f’
 
 werror.hs:10:1: warning: [-Wmissing-signatures (in -Wall)]
-    Top-level binding with no type signature:
-      f :: forall t t1. [t1] -> [t]
+    Top-level binding with no type signature: f :: [t1] -> [t]
 
 werror.hs:10:1: warning: [-Wincomplete-patterns (in -Wextra)]
     Pattern match(es) are non-exhaustive
diff --git a/testsuite/tests/indexed-types/should_compile/T8889.stderr b/testsuite/tests/indexed-types/should_compile/T8889.stderr
index 81359b2..cef00df 100644
--- a/testsuite/tests/indexed-types/should_compile/T8889.stderr
+++ b/testsuite/tests/indexed-types/should_compile/T8889.stderr
@@ -1,6 +1,4 @@
 
 T8889.hs:12:1: warning: [-Wmissing-signatures (in -Wall)]
     Top-level binding with no type signature:
-      f :: forall (f :: * -> *) b a.
-           (C f, C_fmap f a) =>
-           (a -> b) -> f a -> f b
+      f :: (C f, C_fmap f a) => (a -> b) -> f a -> f b
diff --git a/testsuite/tests/parser/should_compile/read014.stderr b/testsuite/tests/parser/should_compile/read014.stderr
index d7c43e5..09e79ee 100644
--- a/testsuite/tests/parser/should_compile/read014.stderr
+++ b/testsuite/tests/parser/should_compile/read014.stderr
@@ -1,7 +1,7 @@
 
 read014.hs:4:1: warning: [-Wmissing-signatures (in -Wall)]
     Top-level binding with no type signature:
-      ng1 :: forall a t. Num a => t -> a -> a
+      ng1 :: Num a => t -> a -> a
 
 read014.hs:4:5: warning: [-Wunused-matches (in -Wextra)]
     Defined but not used: ‘x’
diff --git a/testsuite/tests/rename/should_compile/T12597.hs b/testsuite/tests/rename/should_compile/T12597.hs
new file mode 100644
index 0000000..12769e4
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T12597.hs
@@ -0,0 +1,5 @@
+{-# OPTIONS_GHC -Wmissing-signatures #-}
+
+module T12597 where
+
+f x = x
diff --git a/testsuite/tests/rename/should_compile/T12597.stderr b/testsuite/tests/rename/should_compile/T12597.stderr
new file mode 100644
index 0000000..8364fd0
--- /dev/null
+++ b/testsuite/tests/rename/should_compile/T12597.stderr
@@ -0,0 +1,3 @@
+
+T12597.hs:5:1: warning: [-Wmissing-signatures (in -Wall)]
+    Top-level binding with no type signature: f :: t -> t
diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T
index 8819fd2..023c2eb 100644
--- a/testsuite/tests/rename/should_compile/all.T
+++ b/testsuite/tests/rename/should_compile/all.T
@@ -242,3 +242,4 @@ test('T12127',
      multimod_compile,
      ['T12127', '-v0'])
 test('T12533', normal, compile, [''])
+test('T12597', normal, compile, [''])
diff --git a/testsuite/tests/typecheck/should_compile/T10971a.stderr b/testsuite/tests/typecheck/should_compile/T10971a.stderr
index bfcc3ff..96330fd 100644
--- a/testsuite/tests/typecheck/should_compile/T10971a.stderr
+++ b/testsuite/tests/typecheck/should_compile/T10971a.stderr
@@ -1,6 +1,6 @@
 
 T10971a.hs:7:1: warning: [-Wmissing-signatures (in -Wall)]
-    Top-level binding with no type signature: f :: forall a. [a] -> Int
+    Top-level binding with no type signature: f :: [a] -> Int
 
 T10971a.hs:7:11: warning: [-Wtype-defaults (in -Wall)]
     • Defaulting the following constraint to type ‘[]’
@@ -11,7 +11,7 @@ T10971a.hs:7:11: warning: [-Wtype-defaults (in -Wall)]
 
 T10971a.hs:8:1: warning: [-Wmissing-signatures (in -Wall)]
     Top-level binding with no type signature:
-      g :: forall b a. (a -> b) -> [a] -> [b]
+      g :: (a -> b) -> [a] -> [b]
 
 T10971a.hs:8:6: warning: [-Wname-shadowing (in -Wall)]
     This binding for ‘f’ shadows the existing binding
@@ -26,7 +26,7 @@ T10971a.hs:8:13: warning: [-Wtype-defaults (in -Wall)]
 
 T10971a.hs:9:1: warning: [-Wmissing-signatures (in -Wall)]
     Top-level binding with no type signature:
-      h :: forall b a. (a -> b) -> [a] -> ([b], Int)
+      h :: (a -> b) -> [a] -> ([b], Int)
 
 T10971a.hs:9:6: warning: [-Wname-shadowing (in -Wall)]
     This binding for ‘f’ shadows the existing binding
diff --git a/testsuite/tests/typecheck/should_compile/tc243.stderr b/testsuite/tests/typecheck/should_compile/tc243.stderr
index f96fede..5c5e9b2 100644
--- a/testsuite/tests/typecheck/should_compile/tc243.stderr
+++ b/testsuite/tests/typecheck/should_compile/tc243.stderr
@@ -1,3 +1,3 @@
 
 tc243.hs:10:1: warning: [-Wmissing-signatures (in -Wall)]
-    Top-level binding with no type signature: (.+.) :: forall a. a
+    Top-level binding with no type signature: (.+.) :: a
diff --git a/testsuite/tests/warnings/should_compile/T11077.stderr b/testsuite/tests/warnings/should_compile/T11077.stderr
index fcaa385..ba7d4d8 100644
--- a/testsuite/tests/warnings/should_compile/T11077.stderr
+++ b/testsuite/tests/warnings/should_compile/T11077.stderr
@@ -1,3 +1,3 @@
 
 T11077.hs:3:1: warning: [-Wmissing-exported-sigs]
-    Top-level binding with no type signature: foo :: forall a. a
+    Top-level binding with no type signature: foo :: a



More information about the ghc-commits mailing list