[Git][ghc/ghc][master] 3 commits: Add mainModuleNameIs and demote mainModIs
Marge Bot
gitlab at gitlab.haskell.org
Thu Oct 1 22:35:40 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00
Add mainModuleNameIs and demote mainModIs
Add `mainModuleNameIs` to DynFlags and demote
`mainModIs` to function which uses the homeUnit from DynFlags
it is created from.
- - - - -
fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00
Use HomeUnit for main module without module declaration
- - - - -
dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00
Remove mAIN completely
- - - - -
5 changed files:
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Utils/Backpack.hs
Changes:
=====================================
compiler/GHC/Builtin/Names.hs
=====================================
@@ -610,8 +610,7 @@ gHC_OVER_LABELS = mkBaseModule (fsLit "GHC.OverloadedLabels")
gHC_RECORDS :: Module
gHC_RECORDS = mkBaseModule (fsLit "GHC.Records")
-mAIN, rOOT_MAIN :: Module
-mAIN = mkMainModule_ mAIN_NAME
+rOOT_MAIN :: Module
rOOT_MAIN = mkMainModule (fsLit ":Main") -- Root module for initialisation
mkInteractiveModule :: Int -> Module
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -41,7 +41,7 @@ module GHC.Driver.Session (
dynamicTooMkDynamicDynFlags,
dynamicOutputFile,
sccProfilingEnabled,
- DynFlags(..),
+ DynFlags(..), mainModIs,
FlagSpec(..),
HasDynFlags(..), ContainsDynFlags(..),
RtsOptsEnabled(..),
@@ -240,7 +240,7 @@ import GHC.Unit.Parser
import GHC.Unit.Module
import {-# SOURCE #-} GHC.Driver.Plugins
import {-# SOURCE #-} GHC.Driver.Hooks
-import GHC.Builtin.Names ( mAIN )
+import GHC.Builtin.Names ( mAIN_NAME )
import {-# SOURCE #-} GHC.Unit.State (UnitState, emptyUnitState, UnitDatabase)
import GHC.Driver.Phases ( Phase(..), phaseInputExt )
import GHC.Driver.Flags
@@ -514,7 +514,7 @@ data DynFlags = DynFlags {
historySize :: Int, -- ^ Simplification history size
importPaths :: [FilePath],
- mainModIs :: Module,
+ mainModuleNameIs :: ModuleName,
mainFunIs :: Maybe String,
reductionDepth :: IntWithInf, -- ^ Typechecker maximum stack depth
solverIterations :: IntWithInf, -- ^ Number of iterations in the constraints solver
@@ -1188,7 +1188,7 @@ defaultDynFlags mySettings llvmConfig =
ghcHeapSize = Nothing,
importPaths = ["."],
- mainModIs = mAIN,
+ mainModuleNameIs = mAIN_NAME,
mainFunIs = Nothing,
reductionDepth = treatZeroAsInf mAX_REDUCTION_DEPTH,
solverIterations = treatZeroAsInf mAX_SOLVER_ITERATIONS,
@@ -1665,6 +1665,9 @@ lang_set dflags lang =
extensionFlags = flattenExtensionFlags lang (extensions dflags)
}
+mainModIs :: DynFlags -> Module
+mainModIs dflags = mkHomeModule (mkHomeUnitFromFlags dflags) (mainModuleNameIs dflags)
+
-- | Set the Haskell language standard to use
setLanguage :: Language -> DynP ()
setLanguage l = upd (`lang_set` Just l)
@@ -4505,10 +4508,10 @@ setMainIs arg
| not (null main_fn) && isLower (head main_fn)
-- The arg looked like "Foo.Bar.baz"
= upd $ \d -> d { mainFunIs = Just main_fn,
- mainModIs = mkModule mainUnit (mkModuleName main_mod) }
+ mainModuleNameIs = mkModuleName main_mod }
| isUpper (head arg) -- The arg looked like "Foo" or "Foo.Bar"
- = upd $ \d -> d { mainModIs = mkModule mainUnit (mkModuleName arg) }
+ = upd $ \d -> d { mainModuleNameIs = mkModuleName arg }
| otherwise -- The arg looked like "baz"
= upd $ \d -> d { mainFunIs = Just arg }
=====================================
compiler/GHC/Iface/Recomp/Flags.hs
=====================================
@@ -34,7 +34,7 @@ fingerprintDynFlags :: DynFlags -> Module
-> IO Fingerprint
fingerprintDynFlags dflags at DynFlags{..} this_mod nameio =
- let mainis = if mainModIs == this_mod then Just mainFunIs else Nothing
+ let mainis = if mainModIs dflags == this_mod then Just mainFunIs else Nothing
-- see #5878
-- pkgopts = (homeUnit home_unit, sort $ packageFlags dflags)
safeHs = setSafeMode safeHaskell
=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -194,7 +194,7 @@ tcRnModule hsc_env mod_sum save_rn_syntax
= (mkHomeModule home_unit mod, mod_loc)
| otherwise -- 'module M where' is omitted
- = (mAIN, srcLocSpan (srcSpanStart loc))
+ = (mkHomeModule home_unit mAIN_NAME, srcLocSpan (srcSpanStart loc))
=====================================
compiler/GHC/Tc/Utils/Backpack.hs
=====================================
@@ -58,7 +58,6 @@ import GHC.Data.Maybe
import GHC.Tc.Utils.Env
import GHC.Types.Var
import GHC.Iface.Syntax
-import GHC.Builtin.Names
import qualified Data.Map as Map
import GHC.Driver.Finder
@@ -346,7 +345,7 @@ tcRnCheckUnit hsc_env uid =
initTc hsc_env
HsigFile -- bogus
False
- mAIN -- bogus
+ (mainModIs dflags)
(realSrcLocSpan (mkRealSrcLoc (fsLit loc_str) 0 0)) -- bogus
$ checkUnit uid
where
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e393f213f5ccff4fd6034d5294e51aa5a2720890...dca1cb22cab4fa7f5937e9ffdc0ee32313dbd01c
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e393f213f5ccff4fd6034d5294e51aa5a2720890...dca1cb22cab4fa7f5937e9ffdc0ee32313dbd01c
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/20201001/244bfc5c/attachment-0001.html>
More information about the ghc-commits
mailing list