[commit: ghc] ghc-8.0: Improved error message about exported type operators. (d2744a3)

git at git.haskell.org git at git.haskell.org
Thu Feb 18 12:02:53 UTC 2016


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

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

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

commit d2744a3eb6457aa4043986c20685b9ecf8953612
Author: Ulya Trofimovich <skvadrik at gmail.com>
Date:   Tue Feb 16 22:41:50 2016 +0100

    Improved error message about exported type operators.
    
    There is ambiguty between (1) type constructors and (2) data
    constructors in export lists, e.g. '%%' can stand for both of them. This
    ambiguity is resolved in favor of (2).
    
    If the exported data constructor is not in scope, but type constructor
    with the same name is in scope, GHC should suggest adding 'type' keyword
    to resolve ambiguity in favor of (1) and enabling 'TypeOperators'
    extension.
    
    The patch only extends the error message.
    
    See Trac #11432.
    
    Test Plan: `make test`
    
    Reviewers: simonpj, bgamari, austin
    
    Reviewed By: simonpj
    
    Subscribers: mpickering, thomie, goldfire, kosmikus
    
    Differential Revision: https://phabricator.haskell.org/D1902
    
    GHC Trac Issues: #11432
    
    (cherry picked from commit 693a54ea7ac6bdd229e0a297fc023d25263077b9)


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

d2744a3eb6457aa4043986c20685b9ecf8953612
 compiler/rename/RnEnv.hs             | 23 ++++++++++++++++++++++-
 compiler/rename/RnNames.hs           |  4 ++--
 testsuite/tests/module/T11432.hs     |  9 +++++++++
 testsuite/tests/module/T11432.stderr | 10 ++++++++++
 testsuite/tests/module/all.T         |  1 +
 testsuite/tests/module/mod89.stderr  |  0
 6 files changed, 44 insertions(+), 3 deletions(-)

diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index 868712b..5d74d7c 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -13,7 +13,7 @@ module RnEnv (
         lookupLocalOccRn_maybe, lookupInfoOccRn,
         lookupLocalOccThLvl_maybe,
         lookupTypeOccRn, lookupKindOccRn,
-        lookupGlobalOccRn, lookupGlobalOccRn_maybe,
+        lookupGlobalOccRn, lookupGlobalOccRnExport, lookupGlobalOccRn_maybe,
         lookupOccRn_overloaded, lookupGlobalOccRn_overloaded,
         reportUnboundName, unknownNameSuggestions,
         addNameClashErrRn,
@@ -853,6 +853,27 @@ lookupGlobalOccRn rdr_name
            Nothing -> do { traceRn (text "lookupGlobalOccRn" <+> ppr rdr_name)
                          ; unboundName WL_Global rdr_name } }
 
+-- like lookupGlobalOccRn but suggests adding 'type' keyword
+-- to export type constructors mistaken for data constructors
+lookupGlobalOccRnExport :: RdrName -> RnM Name
+lookupGlobalOccRnExport rdr_name
+  = do { mb_name <- lookupGlobalOccRn_maybe rdr_name
+       ; case mb_name of
+           Just n  -> return n
+           Nothing -> do { env <- getGlobalRdrEnv
+                         ; let tycon = setOccNameSpace tcClsName (rdrNameOcc rdr_name)
+                               msg = case lookupOccEnv env tycon of
+                                   Just (gre : _) -> make_msg gre
+                                   _              -> Outputable.empty
+                               make_msg gre = hang
+                                   (hsep [text "Note: use",
+                                       quotes (text "type"),
+                                       text "keyword to export type constructor",
+                                       quotes (ppr (gre_name gre))])
+                                   2 (vcat [pprNameProvenance gre,
+                                       text "(requires TypeOperators extension)"])
+                         ; unboundNameX WL_Global rdr_name msg } }
+
 lookupInfoOccRn :: RdrName -> RnM [Name]
 -- lookupInfoOccRn is intended for use in GHCi's ":info" command
 -- It finds all the GREs that RdrName could mean, not complaining
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 7f89025..d8e08e2 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1346,7 +1346,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
     lookup_ie_with :: IE RdrName -> Located RdrName -> [Located RdrName]
                    -> RnM (Located Name, [Located Name], [Name], [FieldLabel])
     lookup_ie_with ie (L l rdr) sub_rdrs
-        = do name <- lookupGlobalOccRn rdr
+        = do name <- lookupGlobalOccRnExport rdr
              let gres = findChildren kids_env name
                  mchildren =
                   lookupChildren (map classifyGRE (gres ++ pat_syns)) sub_rdrs
@@ -1366,7 +1366,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod
     lookup_ie_all :: IE RdrName -> Located RdrName
                   -> RnM (Located Name, [Name], [FieldLabel])
     lookup_ie_all ie (L l rdr) =
-          do name <- lookupGlobalOccRn rdr
+          do name <- lookupGlobalOccRnExport rdr
              let gres = findChildren kids_env name
                  (non_flds, flds) = classifyGREs gres
              addUsedKids rdr gres
diff --git a/testsuite/tests/module/T11432.hs b/testsuite/tests/module/T11432.hs
new file mode 100644
index 0000000..408935d
--- /dev/null
+++ b/testsuite/tests/module/T11432.hs
@@ -0,0 +1,9 @@
+{-
+We expect to get a suggestion to add 'type' keyword
+and enable TypeOperators extension.
+-}
+
+{-# LANGUAGE TypeOperators #-}
+module T11432 ((-.->)(..)) where
+
+newtype (f -.-> g) a = Fn { apFn :: f a -> g a }
diff --git a/testsuite/tests/module/T11432.stderr b/testsuite/tests/module/T11432.stderr
new file mode 100644
index 0000000..bf2a58b
--- /dev/null
+++ b/testsuite/tests/module/T11432.stderr
@@ -0,0 +1,10 @@
+
+T11432.hs:7:16:
+    Not in scope: ‘-.->’
+    Note: use ‘type’ keyword to export type constructor ‘-.->’
+      defined at T11432.hs:9:1
+      (requires TypeOperators extension)
+
+T11432.hs:7:16:
+    The export item ‘(-.->)(..)’
+    attempts to export constructors or class methods that are not visible here
diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T
index cd1bdac..e6446fe 100644
--- a/testsuite/tests/module/all.T
+++ b/testsuite/tests/module/all.T
@@ -347,3 +347,4 @@ test('T9061', normal, compile, [''])
 test('T9997', normal, compile, [''])
 test('T10233', extra_clean(['T01233a.hi', 'T01233a.o']),
      multimod_compile, ['T10233', '-v0'])
+test('T11432', normal, compile_fail, [''])



More information about the ghc-commits mailing list