[commit: ghc] master: Parenthesise TypeOperator in import hints (b5c9426)

git at git.haskell.org git at git.haskell.org
Thu Jul 23 12:55:10 UTC 2015


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

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

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

commit b5c94262fa79f735334165c53667f113e07df5e1
Author: Thomas Winant <thomas.winant at cs.kuleuven.be>
Date:   Thu Jul 23 11:43:21 2015 +0200

    Parenthesise TypeOperator in import hints
    
    When a constructor was mistakenly imported directly instead of as a
    constructor of a data type, a hint will be shown on how to correctly
    import
    it. Just like the constructor, the data type should be surrounded in
    parentheses if it is an operator (TypeOperator in this case).
    
    Instead of:
    
        error:
            In module ‘Data.Type.Equality’:
              ‘Refl’ is a data constructor of ‘:~:’
            To import it use
              ‘import’ Data.Type.Equality( :~:( Refl ) )
            or
              ‘import’ Data.Type.Equality( :~:(..) )
    
    Print:
    
        error:
            In module ‘Data.Type.Equality’:
              ‘Refl’ is a data constructor of ‘(:~:)’
            To import it use
              ‘import’ Data.Type.Equality( (:~:)( Refl ) )
            or
              ‘import’ Data.Type.Equality( (:~:)(..) )
    
    Test Plan: pass new test
    
    Reviewers: austin, bgamari, simonpj
    
    Reviewed By: simonpj
    
    Subscribers: simonpj, thomie
    
    Differential Revision: https://phabricator.haskell.org/D1093
    
    GHC Trac Issues: #10668


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

b5c94262fa79f735334165c53667f113e07df5e1
 compiler/rename/RnNames.hs                       | 9 +++++----
 testsuite/tests/rename/should_fail/T10668.hs     | 3 +++
 testsuite/tests/rename/should_fail/T10668.stderr | 8 ++++++++
 testsuite/tests/rename/should_fail/all.T         | 1 +
 4 files changed, 17 insertions(+), 4 deletions(-)

diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 872f4ff..0c116df 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1654,25 +1654,26 @@ badImportItemErrDataCon :: OccName
                         -> ImpDeclSpec
                         -> IE RdrName
                         -> SDoc
-badImportItemErrDataCon dataType is_boot decl_spec ie
+badImportItemErrDataCon dataType_occ is_boot decl_spec ie
   = vcat [ ptext (sLit "In module")
              <+> quotes (ppr (is_mod decl_spec))
              <+> source_import <> colon
          , nest 2 $ quotes datacon
              <+> ptext (sLit "is a data constructor of")
-             <+> quotes (ppr dataType)
+             <+> quotes dataType
          , ptext (sLit "To import it use")
          , nest 2 $ quotes (ptext (sLit "import"))
              <+> ppr (is_mod decl_spec)
-             <> parens_sp (ppr dataType <> parens_sp datacon)
+             <> parens_sp (dataType <> parens_sp datacon)
          , ptext (sLit "or")
          , nest 2 $ quotes (ptext (sLit "import"))
              <+> ppr (is_mod decl_spec)
-             <> parens_sp (ppr dataType <> ptext (sLit "(..)"))
+             <> parens_sp (dataType <> ptext (sLit "(..)"))
          ]
   where
     datacon_occ = rdrNameOcc $ ieName ie
     datacon = parenSymOcc datacon_occ (ppr datacon_occ)
+    dataType = parenSymOcc dataType_occ (ppr dataType_occ)
     source_import | is_boot       = ptext (sLit "(hi-boot interface)")
                   | otherwise     = Outputable.empty
     parens_sp d = parens (space <> d <> space)  -- T( f,g )
diff --git a/testsuite/tests/rename/should_fail/T10668.hs b/testsuite/tests/rename/should_fail/T10668.hs
new file mode 100644
index 0000000..111637b
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T10668.hs
@@ -0,0 +1,3 @@
+module T10668 where
+
+import Data.Type.Equality(Refl)
diff --git a/testsuite/tests/rename/should_fail/T10668.stderr b/testsuite/tests/rename/should_fail/T10668.stderr
new file mode 100644
index 0000000..8c96fad
--- /dev/null
+++ b/testsuite/tests/rename/should_fail/T10668.stderr
@@ -0,0 +1,8 @@
+
+T10668.hs:3:27: error:
+    In module ‘Data.Type.Equality’:
+      ‘Refl’ is a data constructor of ‘(:~:)’
+    To import it use
+      ‘import’ Data.Type.Equality( (:~:)( Refl ) )
+    or
+      ‘import’ Data.Type.Equality( (:~:)(..) )
diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T
index bfd81c5..80471a6 100644
--- a/testsuite/tests/rename/should_fail/all.T
+++ b/testsuite/tests/rename/should_fail/all.T
@@ -134,3 +134,4 @@ test('T9032',
      run_command,
      ['$MAKE -s --no-print-directory T9032'])
 test('T10618', normal, compile_fail, [''])
+test('T10668', normal, compile_fail, [''])



More information about the ghc-commits mailing list