[commit: ghc] master: Improve the "main is not defined in Main" message a bit further (58e4f83)

Simon Peyton Jones simonpj at microsoft.com
Tue Apr 16 17:41:21 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

https://github.com/ghc/ghc/commit/58e4f8380cd18c36be087ac1064aa3cffd9b6b24

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

commit 58e4f8380cd18c36be087ac1064aa3cffd9b6b24
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Apr 15 17:39:39 2013 +0100

    Improve the "main is not defined in Main" message a bit further

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

 compiler/typecheck/TcRnDriver.lhs | 40 +++++++++++++++++++++------------------
 1 file changed, 22 insertions(+), 18 deletions(-)

diff --git a/compiler/typecheck/TcRnDriver.lhs b/compiler/typecheck/TcRnDriver.lhs
index 15ccf57..9391197 100644
--- a/compiler/typecheck/TcRnDriver.lhs
+++ b/compiler/typecheck/TcRnDriver.lhs
@@ -1099,32 +1099,36 @@ check_main dflags tcg_env
                 <+> ptext (sLit "is not defined in module") <+> quotes (ppr main_mod)
     pp_main_fn = ppMainFn main_fn
 
+-- | Get the unqualified name of the function to use as the \"main\" for the main module.
+-- Either returns the default name or the one configured on the command line with -main-is
+getMainFun :: DynFlags -> RdrName
+getMainFun dflags = case mainFunIs dflags of
+    		      Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn))
+    		      Nothing -> main_RDR_Unqual
+
+checkMainExported :: TcGblEnv -> TcM ()
+checkMainExported tcg_env
+  = case tcg_main tcg_env of
+      Nothing -> return () -- not the main module
+      Just main_name -> 
+         do { dflags <- getDynFlags
+            ; let main_mod = mainModIs dflags
+            ; checkTc (main_name `elem` concatMap availNames (tcg_exports tcg_env)) $
+                ptext (sLit "The") <+> ppMainFn (nameRdrName main_name) <+>
+                ptext (sLit "is not exported by module") <+> quotes (ppr main_mod) }
+
 ppMainFn :: RdrName -> SDoc
 ppMainFn main_fn
-  | main_fn == main_RDR_Unqual
+  | rdrNameOcc main_fn == mainOcc
   = ptext (sLit "IO action") <+> quotes (ppr main_fn)
   | otherwise
   = ptext (sLit "main IO action") <+> quotes (ppr main_fn)
 
--- | Get the unqualified name of the function to use as the \"main\" for the main module.
--- Either returns the default name or the one configured on the command line with -main-is
-getMainFun :: DynFlags -> RdrName
-getMainFun dflags = case (mainFunIs dflags) of
-    Just fn -> mkRdrUnqual (mkVarOccFS (mkFastString fn))
-    Nothing -> main_RDR_Unqual
-
-checkMainExported :: TcGblEnv -> TcM ()
-checkMainExported tcg_env = do
-  dflags    <- getDynFlags
-  case tcg_main tcg_env of
-    Nothing -> return () -- not the main module
-    Just main_name -> do
-      let main_mod = mainModIs dflags
-      checkTc (main_name `elem` concatMap availNames (tcg_exports tcg_env)) $
-              ptext (sLit "The") <+> ppMainFn (nameRdrName main_name) <+>
-              ptext (sLit "is not exported by module") <+> quotes (ppr main_mod)
+mainOcc :: OccName
+mainOcc = mkVarOccFS (fsLit "main")
 \end{code}
 
+
 Note [Root-main Id]
 ~~~~~~~~~~~~~~~~~~~
 The function that the RTS invokes is always :Main.main, which we call





More information about the ghc-commits mailing list