GhcBuild.hs 22 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546
  1. {-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
  2. {-# OPTIONS_GHC -fno-warn-unused-binds #-}
  3. {-# OPTIONS_GHC -fno-warn-unused-imports #-}
  4. {-# OPTIONS_GHC -fno-warn-unused-matches #-}
  5. {-
  6. There is a lot of code copied from GHC here, and some conditional
  7. compilation. Instead of fixing all warnings and making it much more
  8. difficult to compare the code to the original, just ignore unused
  9. binds and imports.
  10. -}
  11. {-# LANGUAGE CPP #-}
  12. {-# LANGUAGE PatternGuards #-}
  13. {-# LANGUAGE ScopedTypeVariables #-}
  14. {-
  15. build package with the GHC API
  16. -}
  17. module GhcBuild (getBuildFlags, buildPackage, getPackageArgs) where
  18. import qualified Control.Exception as Ex
  19. import Control.Monad (when)
  20. import Data.IORef
  21. import System.Process (rawSystem)
  22. import System.Environment (getEnvironment)
  23. import CmdLineParser
  24. import Data.Char (toLower)
  25. import Data.List (isPrefixOf, isSuffixOf, partition)
  26. import Data.Maybe (fromMaybe)
  27. import DriverPhases (Phase (..), anyHsc, isHaskellSrcFilename,
  28. isSourceFilename, startPhase)
  29. import DriverPipeline (compileFile, link, linkBinary, oneShot)
  30. import DynFlags (DynFlags, compilerInfo)
  31. import qualified DynFlags
  32. import qualified DynFlags as DF
  33. import qualified GHC
  34. import GHC.Paths (libdir)
  35. import HscTypes (HscEnv (..), emptyHomePackageTable)
  36. import qualified Module
  37. import MonadUtils (liftIO)
  38. import Panic (throwGhcException, panic)
  39. import SrcLoc (Located, mkGeneralLocated)
  40. import qualified StaticFlags
  41. #if __GLASGOW_HASKELL__ >= 707
  42. import DynFlags (ldInputs)
  43. #else
  44. import StaticFlags (v_Ld_inputs)
  45. #endif
  46. import System.FilePath (normalise, (</>))
  47. import Util (consIORef, looksLikeModuleName)
  48. {-
  49. This contains a huge hack:
  50. GHC only accepts setting static flags once per process, however it has no way to
  51. get the remaining options from the command line, without setting the static flags.
  52. This code overwrites the IORef to disable the check. This will likely cause
  53. problems if the flags are modified, but fortunately that's relatively uncommon.
  54. -}
  55. getBuildFlags :: IO [Located String]
  56. getBuildFlags = do
  57. argv0 <- fmap read $ readFile "yesod-devel/ghcargs.txt" -- generated by yesod-ghc-wrapper
  58. argv0' <- prependHsenvArgv argv0
  59. let (minusB_args, argv1) = partition ("-B" `isPrefixOf`) argv0'
  60. mbMinusB | null minusB_args = Nothing
  61. | otherwise = Just (drop 2 (last minusB_args))
  62. let argv1' = map (mkGeneralLocated "on the commandline") argv1
  63. writeIORef StaticFlags.v_opt_C_ready False -- the huge hack
  64. (argv2, staticFlagWarnings) <- GHC.parseStaticFlags argv1'
  65. return argv2
  66. prependHsenvArgv :: [String] -> IO [String]
  67. prependHsenvArgv argv = do
  68. env <- getEnvironment
  69. return $ case (lookup "HSENV" env) of
  70. Nothing -> argv
  71. _ -> hsenvArgv ++ argv
  72. where hsenvArgv = words $ fromMaybe "" (lookup "PACKAGE_DB_FOR_GHC" env)
  73. -- construct a command line for loading the right packages
  74. getPackageArgs :: Maybe String -> [Located String] -> IO [String]
  75. getPackageArgs buildDir argv2 = do
  76. (mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
  77. GHC.runGhc (Just libdir) $ do
  78. dflags0 <- GHC.getSessionDynFlags
  79. (dflags1, _, _) <- GHC.parseDynamicFlags dflags0 argv3
  80. let pkgFlags = map convertPkgFlag (GHC.packageFlags dflags1)
  81. ignorePkgFlags =
  82. #if __GLASGOW_HASKELL__ >= 800
  83. map convertIgnorePkgFlag (GHC.ignorePackageFlags dflags1)
  84. #else
  85. []
  86. #endif
  87. trustPkgFlags =
  88. #if __GLASGOW_HASKELL__ >= 800
  89. map convertTrustPkgFlag (GHC.trustFlags dflags1)
  90. #else
  91. []
  92. #endif
  93. hideAll | gopt DF.Opt_HideAllPackages dflags1 = [ "-hide-all-packages"]
  94. | otherwise = []
  95. ownPkg = packageString (DF.thisPackage dflags1)
  96. return (reverse (extra dflags1) ++ hideAll ++ trustPkgFlags ++ ignorePkgFlags ++ pkgFlags ++ [ownPkg])
  97. where
  98. #if __GLASGOW_HASKELL__ >= 800
  99. convertIgnorePkgFlag (DF.IgnorePackage p) = "-ignore-package" ++ p
  100. convertTrustPkgFlag (DF.TrustPackage p) = "-trust" ++ p
  101. convertTrustPkgFlag (DF.DistrustPackage p) = "-distrust" ++ p
  102. #else
  103. convertPkgFlag (DF.IgnorePackage p) = "-ignore-package" ++ p
  104. convertPkgFlag (DF.TrustPackage p) = "-trust" ++ p
  105. convertPkgFlag (DF.DistrustPackage p) = "-distrust" ++ p
  106. #endif
  107. #if __GLASGOW_HASKELL__ >= 800
  108. convertPkgFlag (DF.ExposePackage _ (DF.PackageArg p) _) = "-package" ++ p
  109. convertPkgFlag (DF.ExposePackage _ (DF.UnitIdArg p) _) = "-package-id" ++ p
  110. #elif __GLASGOW_HASKELL__ == 710
  111. convertPkgFlag (DF.ExposePackage (DF.PackageArg p) _) = "-package" ++ p
  112. convertPkgFlag (DF.ExposePackage (DF.PackageIdArg p) _) = "-package-id" ++ p
  113. convertPkgFlag (DF.ExposePackage (DF.PackageKeyArg p) _) = "-package-key" ++ p
  114. #else
  115. convertPkgFlag (DF.ExposePackage p) = "-package" ++ p
  116. convertPkgFlag (DF.ExposePackageId p) = "-package-id" ++ p
  117. #endif
  118. convertPkgFlag (DF.HidePackage p) = "-hide-package" ++ p
  119. #if __GLASGOW_HASKELL__ >= 800
  120. packageString flags = "-package-id" ++ Module.unitIdString flags
  121. #elif __GLASGOW_HASKELL__ == 710
  122. packageString flags = "-package-key" ++ Module.packageKeyString flags
  123. #else
  124. packageString flags = "-package-id" ++ Module.packageIdString flags ++ "-inplace"
  125. #endif
  126. #if __GLASGOW_HASKELL__ >= 705
  127. extra df = inplaceConf ++ extra'
  128. where
  129. extra' = concatMap convertExtra (extraConfs df)
  130. -- old cabal-install sometimes misses the .inplace db, fix it here
  131. inplaceConf
  132. | any (".inplace" `isSuffixOf`) extra' = []
  133. | otherwise = ["-package-db" ++ fromMaybe "dist" buildDir
  134. ++ "/package.conf.inplace"]
  135. extraConfs df = GHC.extraPkgConfs df []
  136. convertExtra DF.GlobalPkgConf = [ ]
  137. convertExtra DF.UserPkgConf = [ ]
  138. convertExtra (DF.PkgConfFile file) = [ "-package-db" ++ file ]
  139. #else
  140. extra df = inplaceConf ++ extra'
  141. where
  142. extra' = map ("-package-conf"++) (GHC.extraPkgConfs df)
  143. -- old cabal-install sometimes misses the .inplace db, fix it here
  144. inplaceConf
  145. | any (".inplace" `isSuffixOf`) extra' = []
  146. | otherwise = ["-package-conf" ++ fromMaybe "dist" buildDir
  147. ++ "/package.conf.inplace"]
  148. #endif
  149. #if __GLASGOW_HASKELL__ >= 707
  150. gopt = DF.gopt
  151. #else
  152. gopt = DF.dopt
  153. #endif
  154. buildPackage :: [Located String] -> FilePath -> FilePath -> IO Bool
  155. buildPackage a ld ar = buildPackage' a ld ar `Ex.catch` \e -> do
  156. putStrLn ("exception building package: " ++ show (e :: Ex.SomeException))
  157. return False
  158. buildPackage' :: [Located String] -> FilePath -> FilePath -> IO Bool
  159. buildPackage' argv2 ld ar = do
  160. (mode, argv3, modeFlagWarnings) <- parseModeFlags argv2
  161. GHC.runGhc (Just libdir) $ do
  162. dflags0 <- GHC.getSessionDynFlags
  163. (dflags1, _, _) <- GHC.parseDynamicFlags dflags0 argv3
  164. let dflags2 = dflags1 { GHC.ghcMode = GHC.CompManager
  165. , GHC.hscTarget = GHC.hscTarget dflags1
  166. , GHC.ghcLink = GHC.LinkBinary
  167. , GHC.verbosity = 1
  168. }
  169. (dflags3, fileish_args, _) <- GHC.parseDynamicFlags dflags2 argv3
  170. GHC.setSessionDynFlags dflags3
  171. let normal_fileish_paths = map (normalise . GHC.unLoc) fileish_args
  172. (srcs, objs) = partition_args normal_fileish_paths [] []
  173. (hs_srcs, non_hs_srcs) = partition haskellish srcs
  174. haskellish (f,Nothing) =
  175. looksLikeModuleName f || isHaskellSrcFilename f || '.' `notElem` f
  176. haskellish (_,Just phase) =
  177. #if MIN_VERSION_ghc(8,0,0)
  178. phase `notElem` [As True, As False, Cc, Cobjc, Cobjcxx, CmmCpp, Cmm, StopLn]
  179. #elif MIN_VERSION_ghc(7,8,3)
  180. phase `notElem` [As True, As False, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm, StopLn]
  181. #elif MIN_VERSION_ghc(7,4,0)
  182. phase `notElem` [As, Cc, Cobjc, Cobjcpp, CmmCpp, Cmm, StopLn]
  183. #else
  184. phase `notElem` [As, Cc, CmmCpp, Cmm, StopLn]
  185. #endif
  186. hsc_env <- GHC.getSession
  187. -- if (null hs_srcs)
  188. -- then liftIO (oneShot hsc_env StopLn srcs)
  189. -- else do
  190. #if MIN_VERSION_ghc(7,2,0)
  191. o_files <- mapM (\x -> liftIO $ compileFile hsc_env StopLn x)
  192. #else
  193. o_files <- mapM (\x -> compileFile hsc_env StopLn x)
  194. #endif
  195. non_hs_srcs
  196. #if __GLASGOW_HASKELL__ >= 707
  197. let dflags4 = dflags3
  198. { ldInputs = map (DF.FileOption "") (reverse o_files)
  199. ++ ldInputs dflags3
  200. }
  201. GHC.setSessionDynFlags dflags4
  202. #else
  203. liftIO $ mapM_ (consIORef v_Ld_inputs) (reverse o_files)
  204. #endif
  205. targets <- mapM (uncurry GHC.guessTarget) hs_srcs
  206. GHC.setTargets targets
  207. ok_flag <- GHC.load GHC.LoadAllTargets
  208. if GHC.failed ok_flag
  209. then return False
  210. else liftIO (linkPkg ld ar) >> return True
  211. linkPkg :: FilePath -> FilePath -> IO ()
  212. linkPkg ld ar = do
  213. arargs <- fmap read $ readFile "yesod-devel/arargs.txt"
  214. rawSystem ar arargs
  215. ldargs <- fmap read $ readFile "yesod-devel/ldargs.txt"
  216. rawSystem ld ldargs
  217. return ()
  218. --------------------------------------------------------------------------------------------
  219. -- stuff below copied from ghc main.hs
  220. --------------------------------------------------------------------------------------------
  221. partition_args :: [String] -> [(String, Maybe Phase)] -> [String]
  222. -> ([(String, Maybe Phase)], [String])
  223. partition_args [] srcs objs = (reverse srcs, reverse objs)
  224. partition_args ("-x":suff:args) srcs objs
  225. | "none" <- suff = partition_args args srcs objs
  226. | StopLn <- phase = partition_args args srcs (slurp ++ objs)
  227. | otherwise = partition_args rest (these_srcs ++ srcs) objs
  228. where phase = startPhase suff
  229. (slurp,rest) = break (== "-x") args
  230. these_srcs = zip slurp (repeat (Just phase))
  231. partition_args (arg:args) srcs objs
  232. | looks_like_an_input arg = partition_args args ((arg,Nothing):srcs) objs
  233. | otherwise = partition_args args srcs (arg:objs)
  234. {-
  235. We split out the object files (.o, .dll) and add them
  236. to v_Ld_inputs for use by the linker.
  237. The following things should be considered compilation manager inputs:
  238. - haskell source files (strings ending in .hs, .lhs or other
  239. haskellish extension),
  240. - module names (not forgetting hierarchical module names),
  241. - and finally we consider everything not containing a '.' to be
  242. a comp manager input, as shorthand for a .hs or .lhs filename.
  243. Everything else is considered to be a linker object, and passed
  244. straight through to the linker.
  245. -}
  246. looks_like_an_input :: String -> Bool
  247. looks_like_an_input m = isSourceFilename m
  248. || looksLikeModuleName m
  249. || '.' `notElem` m
  250. -- Parsing the mode flag
  251. parseModeFlags :: [Located String]
  252. -> IO (Mode,
  253. [Located String],
  254. [Located String])
  255. parseModeFlags args = do
  256. let ((leftover, errs1, warns), (mModeFlag, errs2, flags')) =
  257. runCmdLine (processArgs mode_flags args)
  258. (Nothing, [], [])
  259. mode = case mModeFlag of
  260. Nothing -> doMakeMode
  261. Just (m, _) -> m
  262. errs = errs1 ++ map (mkGeneralLocated "on the commandline") errs2
  263. #if __GLASGOW_HASKELL__ >= 710
  264. errorsToGhcException' = errorsToGhcException . map (\(GHC.L _ e) -> ("on the commandline", e))
  265. #else
  266. errorsToGhcException' = errorsToGhcException
  267. #endif
  268. when (not (null errs)) $ throwGhcException $ errorsToGhcException' errs
  269. return (mode, flags' ++ leftover, warns)
  270. type ModeM = CmdLineP (Maybe (Mode, String), [String], [Located String])
  271. -- mode flags sometimes give rise to new DynFlags (eg. -C, see below)
  272. -- so we collect the new ones and return them.
  273. mode_flags :: [Flag ModeM]
  274. mode_flags =
  275. [ ------- help / version ----------------------------------------------
  276. mkFlag "?" (PassFlag (setMode showGhcUsageMode))
  277. , mkFlag "-help" (PassFlag (setMode showGhcUsageMode))
  278. , mkFlag "V" (PassFlag (setMode showVersionMode))
  279. , mkFlag "-version" (PassFlag (setMode showVersionMode))
  280. , mkFlag "-numeric-version" (PassFlag (setMode showNumVersionMode))
  281. , mkFlag "-info" (PassFlag (setMode showInfoMode))
  282. , mkFlag "-supported-languages" (PassFlag (setMode showSupportedExtensionsMode))
  283. , mkFlag "-supported-extensions" (PassFlag (setMode showSupportedExtensionsMode))
  284. ] ++
  285. [ mkFlag k' (PassFlag (setMode (printSetting k)))
  286. | k <- ["Project version",
  287. "Booter version",
  288. "Stage",
  289. "Build platform",
  290. "Host platform",
  291. "Target platform",
  292. "Have interpreter",
  293. "Object splitting supported",
  294. "Have native code generator",
  295. "Support SMP",
  296. "Unregisterised",
  297. "Tables next to code",
  298. "RTS ways",
  299. "Leading underscore",
  300. "Debug on",
  301. "LibDir",
  302. "Global Package DB",
  303. "C compiler flags",
  304. "Gcc Linker flags",
  305. "Ld Linker flags"],
  306. let k' = "-print-" ++ map (replaceSpace . toLower) k
  307. replaceSpace ' ' = '-'
  308. replaceSpace c = c
  309. ] ++
  310. ------- interfaces ----------------------------------------------------
  311. [ mkFlag "-show-iface" (HasArg (\f -> setMode (showInterfaceMode f)
  312. "--show-iface"))
  313. ------- primary modes ------------------------------------------------
  314. , mkFlag "c" (PassFlag (\f -> do setMode (stopBeforeMode StopLn) f
  315. addFlag "-no-link" f))
  316. , mkFlag "M" (PassFlag (setMode doMkDependHSMode))
  317. , mkFlag "E" (PassFlag (setMode (stopBeforeMode anyHsc)))
  318. , mkFlag "C" (PassFlag (\f -> do setMode (stopBeforeMode HCc) f
  319. addFlag "-fvia-C" f))
  320. #if MIN_VERSION_ghc(7,8,3)
  321. , mkFlag "S" (PassFlag (setMode (stopBeforeMode (As True))))
  322. #else
  323. , mkFlag "S" (PassFlag (setMode (stopBeforeMode As)))
  324. #endif
  325. , mkFlag "-make" (PassFlag (setMode doMakeMode))
  326. , mkFlag "-interactive" (PassFlag (setMode doInteractiveMode))
  327. , mkFlag "-abi-hash" (PassFlag (setMode doAbiHashMode))
  328. , mkFlag "e" (SepArg (\s -> setMode (doEvalMode s) "-e"))
  329. ]
  330. #if MIN_VERSION_ghc(7,10,1)
  331. where mkFlag fName fOptKind = Flag fName fOptKind AllModes
  332. #else
  333. where mkFlag fName fOptKind = Flag fName fOptKind
  334. #endif
  335. setMode :: Mode -> String -> EwM ModeM ()
  336. setMode newMode newFlag = liftEwM $ do
  337. (mModeFlag, errs, flags') <- getCmdLineState
  338. let (modeFlag', errs') =
  339. case mModeFlag of
  340. Nothing -> ((newMode, newFlag), errs)
  341. Just (oldMode, oldFlag) ->
  342. case (oldMode, newMode) of
  343. -- -c/--make are allowed together, and mean --make -no-link
  344. _ | isStopLnMode oldMode && isDoMakeMode newMode
  345. || isStopLnMode newMode && isDoMakeMode oldMode ->
  346. ((doMakeMode, "--make"), [])
  347. -- If we have both --help and --interactive then we
  348. -- want showGhciUsage
  349. _ | isShowGhcUsageMode oldMode &&
  350. isDoInteractiveMode newMode ->
  351. ((showGhciUsageMode, oldFlag), [])
  352. | isShowGhcUsageMode newMode &&
  353. isDoInteractiveMode oldMode ->
  354. ((showGhciUsageMode, newFlag), [])
  355. -- Otherwise, --help/--version/--numeric-version always win
  356. | isDominantFlag oldMode -> ((oldMode, oldFlag), [])
  357. | isDominantFlag newMode -> ((newMode, newFlag), [])
  358. -- We need to accumulate eval flags like "-e foo -e bar"
  359. (Right (Right (DoEval esOld)),
  360. Right (Right (DoEval [eNew]))) ->
  361. ((Right (Right (DoEval (eNew : esOld))), oldFlag),
  362. errs)
  363. -- Saying e.g. --interactive --interactive is OK
  364. _ | oldFlag == newFlag -> ((oldMode, oldFlag), errs)
  365. -- Otherwise, complain
  366. _ -> let err = flagMismatchErr oldFlag newFlag
  367. in ((oldMode, oldFlag), err : errs)
  368. putCmdLineState (Just modeFlag', errs', flags')
  369. where isDominantFlag f = isShowGhcUsageMode f ||
  370. isShowGhciUsageMode f ||
  371. isShowVersionMode f ||
  372. isShowNumVersionMode f
  373. flagMismatchErr :: String -> String -> String
  374. flagMismatchErr oldFlag newFlag
  375. = "cannot use `" ++ oldFlag ++ "' with `" ++ newFlag ++ "'"
  376. addFlag :: String -> String -> EwM ModeM ()
  377. addFlag s flag = liftEwM $ do
  378. (m, e, flags') <- getCmdLineState
  379. putCmdLineState (m, e, mkGeneralLocated loc s : flags')
  380. where loc = "addFlag by " ++ flag ++ " on the commandline"
  381. type Mode = Either PreStartupMode PostStartupMode
  382. type PostStartupMode = Either PreLoadMode PostLoadMode
  383. data PreStartupMode
  384. = ShowVersion -- ghc -V/--version
  385. | ShowNumVersion -- ghc --numeric-version
  386. | ShowSupportedExtensions -- ghc --supported-extensions
  387. | Print String -- ghc --print-foo
  388. showVersionMode, showNumVersionMode, showSupportedExtensionsMode :: Mode
  389. showVersionMode = mkPreStartupMode ShowVersion
  390. showNumVersionMode = mkPreStartupMode ShowNumVersion
  391. showSupportedExtensionsMode = mkPreStartupMode ShowSupportedExtensions
  392. mkPreStartupMode :: PreStartupMode -> Mode
  393. mkPreStartupMode = Left
  394. isShowVersionMode :: Mode -> Bool
  395. isShowVersionMode (Left ShowVersion) = True
  396. isShowVersionMode _ = False
  397. isShowNumVersionMode :: Mode -> Bool
  398. isShowNumVersionMode (Left ShowNumVersion) = True
  399. isShowNumVersionMode _ = False
  400. data PreLoadMode
  401. = ShowGhcUsage -- ghc -?
  402. | ShowGhciUsage -- ghci -?
  403. | ShowInfo -- ghc --info
  404. | PrintWithDynFlags (DynFlags -> String) -- ghc --print-foo
  405. showGhcUsageMode, showGhciUsageMode, showInfoMode :: Mode
  406. showGhcUsageMode = mkPreLoadMode ShowGhcUsage
  407. showGhciUsageMode = mkPreLoadMode ShowGhciUsage
  408. showInfoMode = mkPreLoadMode ShowInfo
  409. printSetting :: String -> Mode
  410. printSetting k = mkPreLoadMode (PrintWithDynFlags f)
  411. where f dflags = fromMaybe (panic ("Setting not found: " ++ show k))
  412. #if MIN_VERSION_ghc(7,2,0)
  413. $ lookup k (compilerInfo dflags)
  414. #else
  415. $ fmap convertPrintable (lookup k compilerInfo)
  416. where
  417. convertPrintable (DynFlags.String s) = s
  418. convertPrintable (DynFlags.FromDynFlags f) = f dflags
  419. #endif
  420. mkPreLoadMode :: PreLoadMode -> Mode
  421. mkPreLoadMode = Right . Left
  422. isShowGhcUsageMode :: Mode -> Bool
  423. isShowGhcUsageMode (Right (Left ShowGhcUsage)) = True
  424. isShowGhcUsageMode _ = False
  425. isShowGhciUsageMode :: Mode -> Bool
  426. isShowGhciUsageMode (Right (Left ShowGhciUsage)) = True
  427. isShowGhciUsageMode _ = False
  428. data PostLoadMode
  429. = ShowInterface FilePath -- ghc --show-iface
  430. | DoMkDependHS -- ghc -M
  431. | StopBefore Phase -- ghc -E | -C | -S
  432. -- StopBefore StopLn is the default
  433. | DoMake -- ghc --make
  434. | DoInteractive -- ghc --interactive
  435. | DoEval [String] -- ghc -e foo -e bar => DoEval ["bar", "foo"]
  436. | DoAbiHash -- ghc --abi-hash
  437. doMkDependHSMode, doMakeMode, doInteractiveMode, doAbiHashMode :: Mode
  438. doMkDependHSMode = mkPostLoadMode DoMkDependHS
  439. doMakeMode = mkPostLoadMode DoMake
  440. doInteractiveMode = mkPostLoadMode DoInteractive
  441. doAbiHashMode = mkPostLoadMode DoAbiHash
  442. showInterfaceMode :: FilePath -> Mode
  443. showInterfaceMode fp = mkPostLoadMode (ShowInterface fp)
  444. stopBeforeMode :: Phase -> Mode
  445. stopBeforeMode phase = mkPostLoadMode (StopBefore phase)
  446. doEvalMode :: String -> Mode
  447. doEvalMode str = mkPostLoadMode (DoEval [str])
  448. mkPostLoadMode :: PostLoadMode -> Mode
  449. mkPostLoadMode = Right . Right
  450. isDoInteractiveMode :: Mode -> Bool
  451. isDoInteractiveMode (Right (Right DoInteractive)) = True
  452. isDoInteractiveMode _ = False
  453. isStopLnMode :: Mode -> Bool
  454. isStopLnMode (Right (Right (StopBefore StopLn))) = True
  455. isStopLnMode _ = False
  456. isDoMakeMode :: Mode -> Bool
  457. isDoMakeMode (Right (Right DoMake)) = True
  458. isDoMakeMode _ = False
  459. #ifdef GHCI
  460. isInteractiveMode :: PostLoadMode -> Bool
  461. isInteractiveMode DoInteractive = True
  462. isInteractiveMode _ = False
  463. #endif
  464. -- isInterpretiveMode: byte-code compiler involved
  465. isInterpretiveMode :: PostLoadMode -> Bool
  466. isInterpretiveMode DoInteractive = True
  467. isInterpretiveMode (DoEval _) = True
  468. isInterpretiveMode _ = False
  469. needsInputsMode :: PostLoadMode -> Bool
  470. needsInputsMode DoMkDependHS = True
  471. needsInputsMode (StopBefore _) = True
  472. needsInputsMode DoMake = True
  473. needsInputsMode _ = False
  474. -- True if we are going to attempt to link in this mode.
  475. -- (we might not actually link, depending on the GhcLink flag)
  476. isLinkMode :: PostLoadMode -> Bool
  477. isLinkMode (StopBefore StopLn) = True
  478. isLinkMode DoMake = True
  479. isLinkMode DoInteractive = True
  480. isLinkMode (DoEval _) = True
  481. isLinkMode _ = False
  482. isCompManagerMode :: PostLoadMode -> Bool
  483. isCompManagerMode DoMake = True
  484. isCompManagerMode DoInteractive = True
  485. isCompManagerMode (DoEval _) = True
  486. isCompManagerMode _ = False