[Git][ghc/ghc][master] Fix minimal imports dump for boot files (fix #18497)
Marge Bot
gitlab at gitlab.haskell.org
Fri Jul 31 02:54:55 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00
Fix minimal imports dump for boot files (fix #18497)
- - - - -
9 changed files:
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Module.hs
- testsuite/tests/rename/should_compile/Makefile
- + testsuite/tests/rename/should_compile/T18497.stdout
- + testsuite/tests/rename/should_compile/T18497_Bar.hs
- + testsuite/tests/rename/should_compile/T18497_Bar.hs-boot
- + testsuite/tests/rename/should_compile/T18497_Foo.hs
- + testsuite/tests/rename/should_compile/T18497_Foo.hs-boot
- testsuite/tests/rename/should_compile/all.T
Changes:
=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -1234,11 +1234,11 @@ lookupChildren all_kids rdr_items
*********************************************************
-}
-reportUnusedNames :: TcGblEnv -> RnM ()
-reportUnusedNames gbl_env
+reportUnusedNames :: TcGblEnv -> HscSource -> RnM ()
+reportUnusedNames gbl_env hsc_src
= do { keep <- readTcRef (tcg_keep gbl_env)
; traceRn "RUN" (ppr (tcg_dus gbl_env))
- ; warnUnusedImportDecls gbl_env
+ ; warnUnusedImportDecls gbl_env hsc_src
; warnUnusedTopBinds $ unused_locals keep
; warnMissingSignatures gbl_env }
where
@@ -1360,8 +1360,8 @@ type ImportDeclUsage
, [GlobalRdrElt] -- What *is* used (normalised)
, [Name] ) -- What is imported but *not* used
-warnUnusedImportDecls :: TcGblEnv -> RnM ()
-warnUnusedImportDecls gbl_env
+warnUnusedImportDecls :: TcGblEnv -> HscSource -> RnM ()
+warnUnusedImportDecls gbl_env hsc_src
= do { uses <- readMutVar (tcg_used_gres gbl_env)
; let user_imports = filterOut
(ideclImplicit . unLoc)
@@ -1383,7 +1383,7 @@ warnUnusedImportDecls gbl_env
mapM_ (warnUnusedImport Opt_WarnUnusedImports fld_env) usage
; whenGOptM Opt_D_dump_minimal_imports $
- printMinimalImports usage }
+ printMinimalImports hsc_src usage }
findImportUsage :: [LImportDecl GhcRn]
-> [GlobalRdrElt]
@@ -1619,9 +1619,9 @@ getMinimalImports = mapM mk_minimal
all_non_overloaded = all (not . flIsOverloaded)
-printMinimalImports :: [ImportDeclUsage] -> RnM ()
+printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM ()
-- See Note [Printing minimal imports]
-printMinimalImports imports_w_usage
+printMinimalImports hsc_src imports_w_usage
= do { imports' <- getMinimalImports imports_w_usage
; this_mod <- getModule
; dflags <- getDynFlags
@@ -1638,7 +1638,11 @@ printMinimalImports imports_w_usage
| Just d <- dumpDir dflags = d </> basefn
| otherwise = basefn
where
- basefn = moduleNameString (moduleName this_mod) ++ ".imports"
+ suffix = case hsc_src of
+ HsBootFile -> ".imports-boot"
+ HsSrcFile -> ".imports"
+ HsigFile -> ".imports"
+ basefn = moduleNameString (moduleName this_mod) ++ suffix
to_ie_post_rn_var :: (HasOccName name) => Located name -> LIEWrappedName name
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -301,7 +301,7 @@ tcRnModuleTcRnM hsc_env mod_sum
-- Do this /after/ typeinference, so that when reporting
-- a function with no type signature we can give the
-- inferred type
- reportUnusedNames tcg_env
+ reportUnusedNames tcg_env hsc_src
; -- add extra source files to tcg_dependent_files
addDependentFiles src_files
; tcg_env <- runTypecheckerPlugin mod_sum hsc_env tcg_env
=====================================
testsuite/tests/rename/should_compile/Makefile
=====================================
@@ -56,3 +56,7 @@ T7969:
'$(TEST_HC)' $(TEST_HC_OPTS) -c T7969a.hs
'$(TEST_HC)' $(TEST_HC_OPTS) -c T7969.hs -ddump-minimal-imports
cat T7969.imports
+
+T18497:
+ '$(TEST_HC)' $(TEST_HC_OPTS) -fno-code T18497_Foo.hs T18497_Bar.hs -ddump-minimal-imports
+ cat T18497_Bar.imports-boot
=====================================
testsuite/tests/rename/should_compile/T18497.stdout
=====================================
@@ -0,0 +1,5 @@
+[1 of 4] Compiling T18497_Foo[boot] ( T18497_Foo.hs-boot, nothing )
+[2 of 4] Compiling T18497_Bar[boot] ( T18497_Bar.hs-boot, nothing )
+[3 of 4] Compiling T18497_Foo ( T18497_Foo.hs, nothing )
+[4 of 4] Compiling T18497_Bar ( T18497_Bar.hs, nothing )
+import {-# SOURCE #-} T18497_Foo ( X )
=====================================
testsuite/tests/rename/should_compile/T18497_Bar.hs
=====================================
@@ -0,0 +1,14 @@
+module T18497_Bar where
+
+import T18497_Foo
+
+data Y = SomeY X | NoY
+
+blah :: Y
+blah = NoY
+
+blip :: Y
+blip = SomeY foo
+
+woop NoX = NoY
+woop (SomeX y _) = y
=====================================
testsuite/tests/rename/should_compile/T18497_Bar.hs-boot
=====================================
@@ -0,0 +1,9 @@
+module T18497_Bar where
+
+import {-# SOURCE #-} T18497_Foo
+
+data Y
+
+blah :: Y
+
+woop :: X -> Y
=====================================
testsuite/tests/rename/should_compile/T18497_Foo.hs
=====================================
@@ -0,0 +1,8 @@
+module T18497_Foo where
+
+import {-# SOURCE #-} T18497_Bar
+
+data X = SomeX Y Y | NoX
+
+foo :: X
+foo = SomeX blah (woop NoX)
=====================================
testsuite/tests/rename/should_compile/T18497_Foo.hs-boot
=====================================
@@ -0,0 +1,5 @@
+module T18497_Foo where
+
+data X
+
+foo :: X
=====================================
testsuite/tests/rename/should_compile/all.T
=====================================
@@ -174,3 +174,4 @@ test('T17244B', normal, compile, [''])
test('T17244C', normal, compile, [''])
test('T17832', [], multimod_compile, ['T17832M1', 'T17832M2'])
test('T17837', normal, compile, [''])
+test('T18497', [], makefile_test, ['T18497'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c274cd530cc42a26028050b75d56b3437e06ec1
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c274cd530cc42a26028050b75d56b3437e06ec1
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200730/2942f93f/attachment-0001.html>
More information about the ghc-commits
mailing list