[commit: ghc] master: Suggest import Data.Kinds when * is out of scope (023f11f)

git at git.haskell.org git at git.haskell.org
Mon Dec 14 14:33:35 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/023f11f562c7d08af121e4dac04ec66418e6923b/ghc

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

commit 023f11f562c7d08af121e4dac04ec66418e6923b
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Mon Dec 14 15:02:54 2015 +0100

    Suggest import Data.Kinds when * is out of scope
    
    With -XTypeInType, `*` must be imported to be used. This patch makes
    sure the user knows this.
    
    But I'm not sure this is the best way to deal with `*`. Feedback welcome
    on either this small fix or the approach to `*`, in general.
    
    You may wish to see `Note [HsAppsTy]` in HsTypes if you want to take a
    broader view.
    
    Test Plan: dependent/should_fail/RenamingStar
    
    Reviewers: simonpj, bgamari, austin
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1610


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

023f11f562c7d08af121e4dac04ec66418e6923b
 compiler/rename/RnEnv.hs                           | 35 ++++++++++++++--------
 .../tests/dependent/should_fail/RenamingStar.hs    |  5 ++++
 .../dependent/should_fail/RenamingStar.stderr      | 11 +++++++
 testsuite/tests/dependent/should_fail/all.T        |  1 +
 4 files changed, 40 insertions(+), 12 deletions(-)

diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index a398e33..4337dbb 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -713,16 +713,12 @@ lookupKindOccRn :: RdrName -> RnM Name
 -- Looking up a name occurring in a kind
 lookupKindOccRn rdr_name
   = do { typeintype <- xoptM Opt_TypeInType
-       ; if | typeintype   -> lookupTypeOccRn rdr_name
-            | is_star      -> return starKindTyConName
-            | is_uni_star  -> return unicodeStarKindTyConName
-            | otherwise    -> lookupOccRn rdr_name }
-  where
+       ; if | typeintype           -> lookupTypeOccRn rdr_name
       -- With -XNoTypeInType, treat any usage of * in kinds as in scope
       -- this is a dirty hack, but then again so was the old * kind.
-    fs_name = occNameFS $ rdrNameOcc rdr_name
-    is_star     = fs_name == fsLit "*"
-    is_uni_star = fs_name == fsLit "★"
+            | is_star rdr_name     -> return starKindTyConName
+            | is_uni_star rdr_name -> return unicodeStarKindTyConName
+            | otherwise            -> lookupOccRn rdr_name }
 
 -- lookupPromotedOccRn looks up an optionally promoted RdrName.
 lookupTypeOccRn :: RdrName -> RnM Name
@@ -731,16 +727,17 @@ lookupTypeOccRn rdr_name
   = do { mb_name <- lookupOccRn_maybe rdr_name
        ; case mb_name of {
              Just name -> return name ;
-             Nothing   -> lookup_demoted rdr_name } }
+             Nothing   -> do { dflags <- getDynFlags
+                             ; lookup_demoted rdr_name dflags } } }
 
-lookup_demoted :: RdrName -> RnM Name
-lookup_demoted rdr_name
+lookup_demoted :: RdrName -> DynFlags -> RnM Name
+lookup_demoted rdr_name dflags
   | Just demoted_rdr <- demoteRdrName rdr_name
     -- Maybe it's the name of a *data* constructor
   = do { data_kinds <- xoptM Opt_DataKinds
        ; mb_demoted_name <- lookupOccRn_maybe demoted_rdr
        ; case mb_demoted_name of
-           Nothing -> reportUnboundName rdr_name
+           Nothing -> unboundNameX WL_Any rdr_name star_info
            Just demoted_name
              | data_kinds ->
              do { whenWOptM Opt_WarnUntickedPromotedConstructors $
@@ -761,6 +758,20 @@ lookup_demoted rdr_name
            , text "instead of"
            , quotes (ppr name) <> dot ]
 
+    star_info
+      | is_star rdr_name || is_uni_star rdr_name
+      = if xopt Opt_TypeInType dflags
+        then text "NB: With TypeInType, you must import" <+>
+             ppr rdr_name <+> text "from Data.Kind"
+        else empty
+
+      | otherwise
+      = empty
+
+is_star, is_uni_star :: RdrName -> Bool
+is_star     = (fsLit "*" ==) . occNameFS . rdrNameOcc
+is_uni_star = (fsLit "★" ==) . occNameFS . rdrNameOcc
+
 {-
 Note [Demotion]
 ~~~~~~~~~~~~~~~
diff --git a/testsuite/tests/dependent/should_fail/RenamingStar.hs b/testsuite/tests/dependent/should_fail/RenamingStar.hs
new file mode 100644
index 0000000..255021c
--- /dev/null
+++ b/testsuite/tests/dependent/should_fail/RenamingStar.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE TypeInType #-}
+
+module RenamingStar where
+
+data Foo :: *
diff --git a/testsuite/tests/dependent/should_fail/RenamingStar.stderr b/testsuite/tests/dependent/should_fail/RenamingStar.stderr
new file mode 100644
index 0000000..5efda69
--- /dev/null
+++ b/testsuite/tests/dependent/should_fail/RenamingStar.stderr
@@ -0,0 +1,11 @@
+
+RenamingStar.hs:5:13: error:
+    Not in scope: type constructor or class ‘*’
+    NB: With TypeInType, you must import * from Data.Kind
+
+RenamingStar.hs:5:13: error:
+    Illegal operator ‘*’ in type ‘*’
+      Use TypeOperators to allow operators in types
+
+RenamingStar.hs:5:13: error:
+    Operator applied to too few arguments: *
diff --git a/testsuite/tests/dependent/should_fail/all.T b/testsuite/tests/dependent/should_fail/all.T
index 8d4b288..8f9c9d0 100644
--- a/testsuite/tests/dependent/should_fail/all.T
+++ b/testsuite/tests/dependent/should_fail/all.T
@@ -7,3 +7,4 @@ test('BadTelescope3', normal, compile_fail, [''])
 test('PromotedClass', normal, compile_fail, [''])
 test('SelfDep', normal, compile_fail, [''])
 test('BadTelescope4', normal, compile_fail, [''])
+test('RenamingStar', normal, compile_fail, [''])



More information about the ghc-commits mailing list