[commit: ghc] master: Refactor printMinimalImports (#15439) (73683f1)
git at git.haskell.org
git at git.haskell.org
Sun Aug 5 15:06:26 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/73683f143d352343b00b1ab4f3abeb38b81794be/ghc
>---------------------------------------------------------------
commit 73683f143d352343b00b1ab4f3abeb38b81794be
Author: vrom911 <vrom911 at gmail.com>
Date: Sun Aug 5 15:28:25 2018 +0200
Refactor printMinimalImports (#15439)
Summary:
Split into getMinimalImports and printMinimalImports.
Export both functions from RnNames module.
Reviewers: bgamari, mpickering
Reviewed By: mpickering
Subscribers: mpickering, rwbarton, carter
GHC Trac Issues: #15439
Differential Revision: https://phabricator.haskell.org/D5045
>---------------------------------------------------------------
73683f143d352343b00b1ab4f3abeb38b81794be
compiler/rename/RnNames.hs | 48 ++++++++++++++++++++++++++--------------------
1 file changed, 27 insertions(+), 21 deletions(-)
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 6b24d80..8d3f183 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -22,6 +22,8 @@ module RnNames (
dodgyMsg,
dodgyMsgInsert,
findImportUsage,
+ getMinimalImports,
+ printMinimalImports,
ImportDeclUsage
) where
@@ -1466,28 +1468,9 @@ decls, and simply trim their import lists. NB that
from it. Instead we just trim to an empty import list
-}
-printMinimalImports :: [ImportDeclUsage] -> RnM ()
--- See Note [Printing minimal imports]
-printMinimalImports imports_w_usage
- = do { imports' <- mapM mk_minimal imports_w_usage
- ; this_mod <- getModule
- ; dflags <- getDynFlags
- ; liftIO $
- do { h <- openFile (mkFilename dflags this_mod) WriteMode
- ; printForUser dflags h neverQualify (vcat (map ppr imports')) }
- -- The neverQualify is important. We are printing Names
- -- but they are in the context of an 'import' decl, and
- -- we never qualify things inside there
- -- E.g. import Blag( f, b )
- -- not import Blag( Blag.f, Blag.g )!
- }
+getMinimalImports :: [ImportDeclUsage] -> RnM [LImportDecl GhcRn]
+getMinimalImports = mapM mk_minimal
where
- mkFilename dflags this_mod
- | Just d <- dumpDir dflags = d </> basefn
- | otherwise = basefn
- where
- basefn = moduleNameString (moduleName this_mod) ++ ".imports"
-
mk_minimal (L l decl, used, unused)
| null unused
, Just (False, _) <- ideclHiding decl
@@ -1538,6 +1521,29 @@ printMinimalImports imports_w_usage
all_non_overloaded = all (not . flIsOverloaded)
+printMinimalImports :: [ImportDeclUsage] -> RnM ()
+-- See Note [Printing minimal imports]
+printMinimalImports imports_w_usage
+ = do { imports' <- getMinimalImports imports_w_usage
+ ; this_mod <- getModule
+ ; dflags <- getDynFlags
+ ; liftIO $
+ do { h <- openFile (mkFilename dflags this_mod) WriteMode
+ ; printForUser dflags h neverQualify (vcat (map ppr imports')) }
+ -- The neverQualify is important. We are printing Names
+ -- but they are in the context of an 'import' decl, and
+ -- we never qualify things inside there
+ -- E.g. import Blag( f, b )
+ -- not import Blag( Blag.f, Blag.g )!
+ }
+ where
+ mkFilename dflags this_mod
+ | Just d <- dumpDir dflags = d </> basefn
+ | otherwise = basefn
+ where
+ basefn = moduleNameString (moduleName this_mod) ++ ".imports"
+
+
to_ie_post_rn_var :: (HasOccName name) => Located name -> LIEWrappedName name
to_ie_post_rn_var (L l n)
| isDataOcc $ occName n = L l (IEPattern (L l n))
More information about the ghc-commits
mailing list