[project @ 2003-05-06 10:25:32 by simonpj]
authorsimonpj <unknown>
Tue, 6 May 2003 10:26:29 +0000 (10:26 +0000)
committersimonpj <unknown>
Tue, 6 May 2003 10:26:29 +0000 (10:26 +0000)
-------------------------------------
Main module exports
-------------------------------------

Make it so that

        module Main where ....

exports everything defined in Main, as the report says it should.

ghc/compiler/parser/Parser.y
ghc/compiler/parser/RdrHsSyn.lhs
ghc/compiler/rename/RnNames.lhs
ghc/compiler/typecheck/TcRnDriver.lhs

index a305995..443d2b3 100644 (file)
@@ -1,6 +1,6 @@
 {-                                                             -*-haskell-*-
 -----------------------------------------------------------------------------
-$Id: Parser.y,v 1.116 2003/02/20 18:33:53 simonpj Exp $
+$Id: Parser.y,v 1.117 2003/05/06 10:25:32 simonpj Exp $
 
 Haskell grammar.
 
@@ -267,7 +267,16 @@ module     :: { RdrNameHsModule }
        : srcloc 'module' modid maybemoddeprec maybeexports 'where' body 
                { HsModule (mkHomeModule $3) Nothing $5 (fst $7) (snd $7) $4 $1 }
        | srcloc body
-               { HsModule (mkHomeModule mAIN_Name) Nothing Nothing 
+               {       -- Behave as if we'd said 
+                       --      module Main( main ) where ...
+                 let
+                       main_RDR_Unqual = mkUnqual varName FSLIT("main")
+                       -- We definitely don't want an Orig RdrName, because
+                       -- main might, in principle, be imported into module Main
+                 in
+                 HsModule (mkHomeModule mAIN_Name) 
+                          Nothing 
+                          (Just [IEVar main_RDR_Unqual])
                           (fst $2) (snd $2) Nothing $1 }
 
 maybemoddeprec :: { Maybe DeprecTxt }
index cdb59b7..4320c28 100644 (file)
@@ -43,6 +43,8 @@ module RdrHsSyn (
        RdrBinding(..),
        RdrMatch(..),
 
+       main_RDR_Unqual,
+
        extractHsTyRdrNames,  extractHsTyRdrTyVars, 
        extractHsCtxtRdrTyVars, extractGenericPatTyVars,
  
@@ -154,6 +156,12 @@ type RdrNameFixitySig              = FixitySig             RdrName
 type RdrNameHsRecordBinds      = HsRecordBinds         RdrName
 \end{code}
 
+\begin{code}
+main_RDR_Unqual :: RdrName
+main_RDR_Unqual = mkUnqual varName FSLIT("main")
+       -- We definitely don't want an Orig RdrName, because
+       -- main might, in principle, be imported into module Main
+\end{code}
 
 %************************************************************************
 %*                                                                     *
index 6eac67c..12eb33a 100644 (file)
@@ -6,7 +6,7 @@
 \begin{code}
 module RnNames (
        rnImports, importsFromLocalDecls, exportsFromAvail,
-       reportUnusedNames, mkModDeps, main_RDR_Unqual
+       reportUnusedNames, mkModDeps
     ) where
 
 #include "HsVersions.h"
@@ -541,27 +541,18 @@ exportsFromAvail exports
 
 exports_from_avail Nothing rdr_env
                   imports@(ImportAvails { imp_env = entity_avail_env })
- = do { this_mod <- getModule ;
-       if moduleName this_mod == mAIN_Name then
-          exports_from_avail (Just [IEVar main_RDR_Unqual]) rdr_env imports
-               -- Behave just as if we'd said module Main(main)
-               -- This is particularly important if we compile module Main,
-               -- but then use ghci to call it... we jolly well expect to
-               -- see 'main'!
-       else 
-               -- Export all locally-defined things
-               -- We do this by filtering the global RdrEnv,
-               -- keeping only things that are (a) qualified,
-               -- (b) locally defined, (c) a 'main' name
-               -- Then we look up in the entity-avail-env
-       return [ lookupAvailEnv entity_avail_env name
+ =     -- Export all locally-defined things
+       -- We do this by filtering the global RdrEnv,
+       -- keeping only things that are (a) qualified,
+       -- (b) locally defined, (c) a 'main' name
+       -- Then we look up in the entity-avail-env
+   return [ lookupAvailEnv entity_avail_env name
               | (rdr_name, gres) <- rdrEnvToList rdr_env,
                 isQual rdr_name,       -- Avoid duplicates
                 GRE { gre_name   = name, 
                       gre_parent = Nothing,    -- Main things only
                       gre_prov   = LocalDef } <- gres
               ]
-    }
 
 exports_from_avail (Just export_items) rdr_env
                   (ImportAvails { imp_qual = mod_avail_env, 
@@ -678,13 +669,6 @@ check_occs ie occs avail
                     returnM occs }
       where
        name_occ = nameOccName name
-
-----------------------------
-main_RDR_Unqual :: RdrName
-main_RDR_Unqual = mkUnqual varName FSLIT("main")
-       -- Don't get a RdrName from PrelNames.mainName, because 
-       -- nameRdrNamegets an Orig RdrName, and we want a Qual or Unqual one.  
-       -- An Unqual one will do just fine
 \end{code}
 
 %*********************************************************
index a6f3331..64b9491 100644 (file)
@@ -28,7 +28,7 @@ import HsSyn          ( HsModule(..), HsBinds(..), MonoBinds(..), HsExpr(..),
                          isSrcRule, collectStmtsBinders
                        )
 import RdrHsSyn                ( RdrNameHsModule, RdrNameHsDecl, RdrNameStmt, RdrNameHsExpr,
-                         emptyGroup, mkGroup, findSplice, addImpDecls )
+                         emptyGroup, mkGroup, findSplice, addImpDecls, main_RDR_Unqual )
 
 import PrelNames       ( iNTERACTIVE, ioTyConName, printName,
                          returnIOName, bindIOName, failIOName, thenIOName, runIOName, 
@@ -70,7 +70,7 @@ import TcSimplify     ( tcSimplifyTop, tcSimplifyInfer )
 import TcTyClsDecls    ( tcTyAndClassDecls )
 
 import RnNames         ( importsFromLocalDecls, rnImports, exportsFromAvail, 
-                         reportUnusedNames, main_RDR_Unqual )
+                         reportUnusedNames )
 import RnIfaces                ( slurpImpDecls, checkVersions, RecompileRequired, outOfDate )
 import RnHiFiles       ( readIface, loadOldIface )
 import RnEnv           ( lookupSrcName, lookupOccRn, plusGlobalRdrEnv,