[commit: ghc] master: Fix trac #15702, as a followon to fix for #13704. (0e7790a)
git at git.haskell.org
git at git.haskell.org
Sat Nov 17 12:53:03 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/0e7790abf7d19d19f84c86dc95e50beb65462d12/ghc
>---------------------------------------------------------------
commit 0e7790abf7d19d19f84c86dc95e50beb65462d12
Author: Chris Smith <cdsmith at gmail.com>
Date: Sat Nov 17 12:40:23 2018 +0100
Fix trac #15702, as a followon to fix for #13704.
Summary:
The effect of this change is that -main-is changes the default
export list for the main module, but does not apply the same
change to non-main modules. This fixes some cases where -main-is
was used to wrap a module that expected that default behavior
(exporting `main`, even when that wasn't the main entry point
name).
Reviewers: mpickering, monoidal, bgamari
Subscribers: rwbarton, carter
GHC Trac Issues: #13704, #15702
Differential Revision: https://phabricator.haskell.org/D5322
>---------------------------------------------------------------
0e7790abf7d19d19f84c86dc95e50beb65462d12
compiler/typecheck/TcRnExports.hs | 6 ++--
docs/users_guide/bugs.rst | 38 +++++++++++++++-------
testsuite/tests/module/{T13704.hs => T13704a.hs} | 0
.../{dynlibs/T5373B.hs => module/T13704b1.hs} | 2 +-
testsuite/tests/module/T13704b2.hs | 7 ++++
testsuite/tests/module/all.T | 3 +-
6 files changed, 41 insertions(+), 15 deletions(-)
diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs
index 1b57608..a2f892b 100644
--- a/compiler/typecheck/TcRnExports.hs
+++ b/compiler/typecheck/TcRnExports.hs
@@ -127,9 +127,11 @@ tcRnExports explicit_mod exports
-- In interactive mode, we behave as if he had
-- written "module Main where ..."
; dflags <- getDynFlags
+ ; let is_main_mod = mainModIs dflags == this_mod
; let default_main = case mainFunIs dflags of
- Just main_fun -> mkUnqual varName (fsLit main_fun)
- Nothing -> main_RDR_Unqual
+ Just main_fun
+ | is_main_mod -> mkUnqual varName (fsLit main_fun)
+ _ -> main_RDR_Unqual
; let real_exports
| explicit_mod = exports
| ghcLink dflags == LinkInMemory = Nothing
diff --git a/docs/users_guide/bugs.rst b/docs/users_guide/bugs.rst
index 0290622..96cdd25 100644
--- a/docs/users_guide/bugs.rst
+++ b/docs/users_guide/bugs.rst
@@ -171,35 +171,51 @@ same context. For example, this is fine: ::
g :: Ord a => a -> Bool
g y = (y <= y) || f True
-.. _infelicities-Modules:
+.. _infelicities-default-exports:
Default Module headers with -main-is
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
-The Haskell2010 report specifies in <https://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-990005.1> that
+The Haskell2010 Report specifies in <https://www.haskell.org/onlinereport/haskell2010/haskellch5.html#x11-990005.1> that
"An abbreviated form of module, consisting only of the module body,
is permitted. If this is used, the header is assumed to be
`module Main(main) where`."
+GHC's ``-main-is`` option can be used to change the name of the top-level entry
+point from ``main`` to any other variable. When compiling the main module and
+``-main-is`` has been used to rename the default entry point, GHC will also use
+the alternate name in the default export list.
+
Consider the following program: ::
-- file: Main.hs
program :: IO ()
program = return ()
-Under the report, this would fail with ``ghc -main-is Main.program Main.hs``
-with the following errors: ::
+GHC will successfully compile this module with
+``ghc -main-is Main.program Main.hs``, because the default export list
+will include ``program`` rather than ``main``, as the Haskell Report
+typically requires.
+
+This change only applies to the main module. Other modules will still export
+``main`` from a default export list, regardless of the ``-main-is`` flag.
+This allows use of ``-main-is`` with existing modules that export ``main`` via
+a default export list, even when ``-main-is`` points to a different entry
+point, as in this example (compiled with ``-main-is MainWrapper.program``). ::
- Main.hs:1:1: error:
- Not in scope: 'main'
- Perhaps you meant 'min' (imported from Prelude)
+ -- file MainWrapper.hs
+ module MainWrapper where
+ import Main
- Main.hs:1:1: error:
- The main IO action 'program' is not exported by module 'Main'
+ program :: IO ()
+ program = putStrLn "Redirecting..." >> main
+
+ -- file Main.hs
+ main :: IO ()
+ main = putStrLn "I am main."
-GHC's flag '-main-is' allows one to change the entry point name so that
-the above example would succeed.
+.. _infelicities-Modules:
Module system and interface files
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
diff --git a/testsuite/tests/module/T13704.hs b/testsuite/tests/module/T13704a.hs
similarity index 100%
rename from testsuite/tests/module/T13704.hs
rename to testsuite/tests/module/T13704a.hs
diff --git a/testsuite/tests/dynlibs/T5373B.hs b/testsuite/tests/module/T13704b1.hs
similarity index 55%
copy from testsuite/tests/dynlibs/T5373B.hs
copy to testsuite/tests/module/T13704b1.hs
index 0570fb1..28b8800 100644
--- a/testsuite/tests/dynlibs/T5373B.hs
+++ b/testsuite/tests/module/T13704b1.hs
@@ -1,4 +1,4 @@
-
main :: IO ()
main = return ()
+-- wrapped by T13704b2.hs
diff --git a/testsuite/tests/module/T13704b2.hs b/testsuite/tests/module/T13704b2.hs
new file mode 100644
index 0000000..d76206f
--- /dev/null
+++ b/testsuite/tests/module/T13704b2.hs
@@ -0,0 +1,7 @@
+module T13704b2 where
+import Main (main)
+
+program :: IO ()
+program = main
+
+-- meant to be compiled with '-main-is T13704b2.program'
diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T
index dbba44f..33ce3ae 100644
--- a/testsuite/tests/module/all.T
+++ b/testsuite/tests/module/all.T
@@ -284,4 +284,5 @@ test('T11970B', normal, compile_fail, [''])
test('MultiExport', normal, compile, [''])
test('T13528', normal, compile, [''])
test('T13622', normal, compile, [''])
-test('T13704', normal, compile, ['-main-is Main.program'])
+test('T13704a', normal, compile, ['-main-is Main.program'])
+test('T13704b', [], multimod_compile, ['T13704b1.hs T13704b2.hs', '-main-is T13704b2.program -v0'])
More information about the ghc-commits
mailing list