summaryrefslogtreecommitdiff
path: root/ghc/Main.hs
diff options
context:
space:
mode:
authorEdward Z. Yang <ezyang@cs.stanford.edu>2015-07-24 15:13:49 -0700
committerEdward Z. Yang <ezyang@cs.stanford.edu>2015-09-21 11:53:56 -0700
commit06d46b1e4507e09eb2a7a04998a92610c8dc6277 (patch)
tree7dc84733d3b6a8313c272c2c8fed4cc0b5d30e90 /ghc/Main.hs
parent09d214dcd8e831c128c684facb7c8da1d63c58bc (diff)
downloadhaskell-06d46b1e4507e09eb2a7a04998a92610c8dc6277.tar.gz
Unify hsig and hs-boot; add preliminary "hs-boot" merging.
This patch drops the file level distinction between hs-boot and hsig; we figure out which one we are compiling based on whether or not there is a corresponding hs file lying around. To make the "import A" syntax continue to work for bare hs-boot files, we also introduce hs-boot merging, which takes an A.hi-boot and converts it to an A.hi when there is no A.hs file in scope. This will be generalized in Backpack to merge multiple A.hi files together; which means we can jettison the "load multiple interface files" functionality. This works automatically for --make, but for one-shot compilation we need a new mode: ghc --merge-requirements A will generate an A.hi/A.o from a local A.hi-boot file; Backpack will extend this mechanism further. Has Haddock submodule update to deal with change in msHsFilePath behavior. - This commit drops support for the hsig extension. Can we support it? It's annoying because the finder code is written with the assumption that where there's an hs-boot file, there's always an hs file too. To support hsig, you'd have to probe two locations. Easier to just not support it. - #10333 affects us, modifying an hs-boot still doesn't trigger recomp. - See compiler/main/Finder.hs: this diff is very skeevy, but it seems to work. - This code cunningly doesn't drop hs-boot files from the "drop hs-boot files" module graph, if they don't have a corresponding hs file. I have no idea if this actually is useful. Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu> Test Plan: validate Reviewers: simonpj, austin, bgamari, spinda Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1098
Diffstat (limited to 'ghc/Main.hs')
-rw-r--r--ghc/Main.hs19
1 files changed, 17 insertions, 2 deletions
diff --git a/ghc/Main.hs b/ghc/Main.hs
index e2c7479008..7ca7481fc3 100644
--- a/ghc/Main.hs
+++ b/ghc/Main.hs
@@ -22,7 +22,7 @@ import CmdLineParser
-- Implementations of the various modes (--show-iface, mkdependHS. etc.)
import LoadIface ( showIface )
import HscMain ( newHscEnv )
-import DriverPipeline ( oneShot, compileFile )
+import DriverPipeline ( oneShot, compileFile, mergeRequirement )
import DriverMkDepend ( doMkDependHS )
#ifdef GHCI
import InteractiveUI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
@@ -156,6 +156,7 @@ main' postLoadMode dflags0 args flagWarnings = do
DoMake -> (CompManager, dflt_target, LinkBinary)
DoMkDependHS -> (MkDepend, dflt_target, LinkBinary)
DoAbiHash -> (OneShot, dflt_target, LinkBinary)
+ DoMergeRequirements -> (OneShot, dflt_target, LinkBinary)
_ -> (OneShot, dflt_target, LinkBinary)
let dflags1 = case lang of
@@ -250,6 +251,7 @@ main' postLoadMode dflags0 args flagWarnings = do
DoInteractive -> ghciUI srcs Nothing
DoEval exprs -> ghciUI srcs $ Just $ reverse exprs
DoAbiHash -> abiHash (map fst srcs)
+ DoMergeRequirements -> doMergeRequirements (map fst srcs)
ShowPackages -> liftIO $ showPackages dflags6
liftIO $ dumpFinalStats dflags6
@@ -455,14 +457,16 @@ data PostLoadMode
| DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"]
| DoAbiHash -- ghc --abi-hash
| ShowPackages -- ghc --show-packages
+ | DoMergeRequirements -- ghc --merge-requirements
doMkDependHSMode, doMakeMode, doInteractiveMode,
- doAbiHashMode, showPackagesMode :: Mode
+ doAbiHashMode, showPackagesMode, doMergeRequirementsMode :: Mode
doMkDependHSMode = mkPostLoadMode DoMkDependHS
doMakeMode = mkPostLoadMode DoMake
doInteractiveMode = mkPostLoadMode DoInteractive
doAbiHashMode = mkPostLoadMode DoAbiHash
showPackagesMode = mkPostLoadMode ShowPackages
+doMergeRequirementsMode = mkPostLoadMode DoMergeRequirements
showInterfaceMode :: FilePath -> Mode
showInterfaceMode fp = mkPostLoadMode (ShowInterface fp)
@@ -598,6 +602,7 @@ mode_flags =
, defFlag "C" (PassFlag (setMode (stopBeforeMode HCc)))
, defFlag "S" (PassFlag (setMode (stopBeforeMode (As False))))
, defFlag "-make" (PassFlag (setMode doMakeMode))
+ , defFlag "-merge-requirements" (PassFlag (setMode doMergeRequirementsMode))
, defFlag "-interactive" (PassFlag (setMode doInteractiveMode))
, defFlag "-abi-hash" (PassFlag (setMode doAbiHashMode))
, defFlag "e" (SepArg (\s -> setMode (doEvalMode s) "-e"))
@@ -698,6 +703,16 @@ doMake srcs = do
when (failed ok_flag) (liftIO $ exitWith (ExitFailure 1))
return ()
+-- ----------------------------------------------------------------------------
+-- Run --merge-requirements mode
+
+doMergeRequirements :: [String] -> Ghc ()
+doMergeRequirements srcs = mapM_ doMergeRequirement srcs
+
+doMergeRequirement :: String -> Ghc ()
+doMergeRequirement src = do
+ hsc_env <- getSession
+ liftIO $ mergeRequirement hsc_env (mkModuleName src)
-- ---------------------------------------------------------------------------
-- --show-iface mode