PageRenderTime 67ms CodeModel.GetById 21ms RepoModel.GetById 0ms app.codeStats 1ms

/compiler/main/DriverPipeline.hs

https://github.com/luite/ghc
Haskell | 2167 lines | 1369 code | 333 blank | 465 comment | 142 complexity | 3deaaf6a63c69ff7425dd39863e85813 MD5 | raw file
  1. {-# OPTIONS -fno-cse #-}
  2. {-# LANGUAGE NamedFieldPuns #-}
  3. -- -fno-cse is needed for GLOBAL_VAR's to behave properly
  4. -----------------------------------------------------------------------------
  5. --
  6. -- GHC Driver
  7. --
  8. -- (c) The University of Glasgow 2005
  9. --
  10. -----------------------------------------------------------------------------
  11. module DriverPipeline (
  12. -- Run a series of compilation steps in a pipeline, for a
  13. -- collection of source files.
  14. oneShot, compileFile,
  15. -- Interfaces for the batch-mode driver
  16. linkBinary,
  17. -- Interfaces for the compilation manager (interpreted/batch-mode)
  18. preprocess,
  19. compileOne, compileOne',
  20. link,
  21. ) where
  22. #include "HsVersions.h"
  23. import Packages
  24. import HeaderInfo
  25. import DriverPhases
  26. import SysTools
  27. import HscMain
  28. import Finder
  29. import HscTypes
  30. import Outputable
  31. import Module
  32. import UniqFM ( eltsUFM )
  33. import ErrUtils
  34. import DynFlags
  35. import Config
  36. import Panic
  37. import Util
  38. import StringBuffer ( hGetStringBuffer )
  39. import BasicTypes ( SuccessFlag(..) )
  40. import Maybes ( expectJust )
  41. import ParserCoreUtils ( getCoreModuleName )
  42. import SrcLoc
  43. import FastString
  44. import LlvmCodeGen ( llvmFixupAsm )
  45. import MonadUtils
  46. import Platform
  47. import TcRnTypes
  48. import Exception
  49. import Data.IORef ( readIORef )
  50. import System.Directory
  51. import System.FilePath
  52. import System.IO
  53. import Control.Monad
  54. import Data.List ( isSuffixOf )
  55. import Data.Maybe
  56. import System.Environment
  57. import Data.Char
  58. -- ---------------------------------------------------------------------------
  59. -- Pre-process
  60. -- | Just preprocess a file, put the result in a temp. file (used by the
  61. -- compilation manager during the summary phase).
  62. --
  63. -- We return the augmented DynFlags, because they contain the result
  64. -- of slurping in the OPTIONS pragmas
  65. preprocess :: HscEnv
  66. -> (FilePath, Maybe Phase) -- ^ filename and starting phase
  67. -> IO (DynFlags, FilePath)
  68. preprocess hsc_env (filename, mb_phase) =
  69. ASSERT2(isJust mb_phase || isHaskellSrcFilename filename, text filename)
  70. runPipeline anyHsc hsc_env (filename, fmap RealPhase mb_phase)
  71. Nothing Temporary Nothing{-no ModLocation-} Nothing{-no stub-}
  72. -- ---------------------------------------------------------------------------
  73. -- | Compile
  74. --
  75. -- Compile a single module, under the control of the compilation manager.
  76. --
  77. -- This is the interface between the compilation manager and the
  78. -- compiler proper (hsc), where we deal with tedious details like
  79. -- reading the OPTIONS pragma from the source file, converting the
  80. -- C or assembly that GHC produces into an object file, and compiling
  81. -- FFI stub files.
  82. --
  83. -- NB. No old interface can also mean that the source has changed.
  84. compileOne :: HscEnv
  85. -> ModSummary -- ^ summary for module being compiled
  86. -> Int -- ^ module N ...
  87. -> Int -- ^ ... of M
  88. -> Maybe ModIface -- ^ old interface, if we have one
  89. -> Maybe Linkable -- ^ old linkable, if we have one
  90. -> SourceModified
  91. -> IO HomeModInfo -- ^ the complete HomeModInfo, if successful
  92. compileOne = compileOne' Nothing (Just batchMsg)
  93. compileOne' :: Maybe TcGblEnv
  94. -> Maybe Messager
  95. -> HscEnv
  96. -> ModSummary -- ^ summary for module being compiled
  97. -> Int -- ^ module N ...
  98. -> Int -- ^ ... of M
  99. -> Maybe ModIface -- ^ old interface, if we have one
  100. -> Maybe Linkable -- ^ old linkable, if we have one
  101. -> SourceModified
  102. -> IO HomeModInfo -- ^ the complete HomeModInfo, if successful
  103. compileOne' m_tc_result mHscMessage
  104. hsc_env0 summary mod_index nmods mb_old_iface maybe_old_linkable
  105. source_modified0
  106. = do
  107. let dflags0 = ms_hspp_opts summary
  108. this_mod = ms_mod summary
  109. src_flavour = ms_hsc_src summary
  110. location = ms_location summary
  111. input_fn = expectJust "compile:hs" (ml_hs_file location)
  112. input_fnpp = ms_hspp_file summary
  113. debugTraceMsg dflags0 2 (text "compile: input file" <+> text input_fnpp)
  114. let basename = dropExtension input_fn
  115. -- We add the directory in which the .hs files resides) to the import path.
  116. -- This is needed when we try to compile the .hc file later, if it
  117. -- imports a _stub.h file that we created here.
  118. let current_dir = takeDirectory basename
  119. old_paths = includePaths dflags0
  120. dflags = dflags0 { includePaths = current_dir : old_paths }
  121. hsc_env = hsc_env0 {hsc_dflags = dflags}
  122. -- Figure out what lang we're generating
  123. let hsc_lang = hscTarget dflags
  124. -- ... and what the next phase should be
  125. let next_phase = hscPostBackendPhase dflags src_flavour hsc_lang
  126. -- ... and what file to generate the output into
  127. output_fn <- getOutputFilename next_phase
  128. Temporary basename dflags next_phase (Just location)
  129. let extCore_filename = basename ++ ".hcr"
  130. -- -fforce-recomp should also work with --make
  131. let force_recomp = gopt Opt_ForceRecomp dflags
  132. source_modified
  133. | force_recomp || isNothing maybe_old_linkable = SourceModified
  134. | otherwise = source_modified0
  135. object_filename = ml_obj_file location
  136. let always_do_basic_recompilation_check = case hsc_lang of
  137. HscInterpreted -> True
  138. _ -> False
  139. e <- genericHscCompileGetFrontendResult
  140. always_do_basic_recompilation_check
  141. m_tc_result mHscMessage
  142. hsc_env summary source_modified mb_old_iface (mod_index, nmods)
  143. case e of
  144. Left iface ->
  145. do details <- genModDetails hsc_env iface
  146. MASSERT (isJust maybe_old_linkable)
  147. return (HomeModInfo{ hm_details = details,
  148. hm_iface = iface,
  149. hm_linkable = maybe_old_linkable })
  150. Right (tc_result, mb_old_hash) ->
  151. -- run the compiler
  152. case hsc_lang of
  153. HscInterpreted ->
  154. case ms_hsc_src summary of
  155. HsBootFile ->
  156. do (iface, _changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
  157. return (HomeModInfo{ hm_details = details,
  158. hm_iface = iface,
  159. hm_linkable = maybe_old_linkable })
  160. _ -> do guts0 <- hscDesugar hsc_env summary tc_result
  161. guts <- hscSimplify hsc_env guts0
  162. (iface, _changed, details, cgguts) <- hscNormalIface hsc_env extCore_filename guts mb_old_hash
  163. (hasStub, comp_bc, modBreaks) <- hscInteractive hsc_env cgguts summary
  164. stub_o <- case hasStub of
  165. Nothing -> return []
  166. Just stub_c -> do
  167. stub_o <- compileStub hsc_env stub_c
  168. return [DotO stub_o]
  169. let hs_unlinked = [BCOs comp_bc modBreaks]
  170. unlinked_time = ms_hs_date summary
  171. -- Why do we use the timestamp of the source file here,
  172. -- rather than the current time? This works better in
  173. -- the case where the local clock is out of sync
  174. -- with the filesystem's clock. It's just as accurate:
  175. -- if the source is modified, then the linkable will
  176. -- be out of date.
  177. let linkable = LM unlinked_time this_mod
  178. (hs_unlinked ++ stub_o)
  179. return (HomeModInfo{ hm_details = details,
  180. hm_iface = iface,
  181. hm_linkable = Just linkable })
  182. HscNothing ->
  183. do (iface, _changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
  184. let linkable = if isHsBoot src_flavour
  185. then maybe_old_linkable
  186. else Just (LM (ms_hs_date summary) this_mod [])
  187. return (HomeModInfo{ hm_details = details,
  188. hm_iface = iface,
  189. hm_linkable = linkable })
  190. _ ->
  191. case ms_hsc_src summary of
  192. HsBootFile ->
  193. do (iface, changed, details) <- hscSimpleIface hsc_env tc_result mb_old_hash
  194. hscWriteIface dflags iface changed summary
  195. touchObjectFile dflags object_filename
  196. return (HomeModInfo{ hm_details = details,
  197. hm_iface = iface,
  198. hm_linkable = maybe_old_linkable })
  199. _ -> do guts0 <- hscDesugar hsc_env summary tc_result
  200. guts <- hscSimplify hsc_env guts0
  201. (iface, changed, details, cgguts) <- hscNormalIface hsc_env extCore_filename guts mb_old_hash
  202. hscWriteIface dflags iface changed summary
  203. -- We're in --make mode: finish the compilation pipeline.
  204. let mod_name = ms_mod_name summary
  205. _ <- runPipeline StopLn hsc_env
  206. (output_fn,
  207. Just (HscOut src_flavour mod_name (HscRecomp cgguts summary)))
  208. (Just basename)
  209. Persistent
  210. (Just location)
  211. Nothing
  212. -- The object filename comes from the ModLocation
  213. o_time <- getModificationUTCTime object_filename
  214. let linkable = LM o_time this_mod [DotO object_filename]
  215. return (HomeModInfo{ hm_details = details,
  216. hm_iface = iface,
  217. hm_linkable = Just linkable })
  218. -----------------------------------------------------------------------------
  219. -- stub .h and .c files (for foreign export support)
  220. -- The _stub.c file is derived from the haskell source file, possibly taking
  221. -- into account the -stubdir option.
  222. --
  223. -- The object file created by compiling the _stub.c file is put into a
  224. -- temporary file, which will be later combined with the main .o file
  225. -- (see the MergeStubs phase).
  226. compileStub :: HscEnv -> FilePath -> IO FilePath
  227. compileStub hsc_env stub_c = do
  228. (_, stub_o) <- runPipeline StopLn hsc_env (stub_c,Nothing) Nothing
  229. Temporary Nothing{-no ModLocation-} Nothing
  230. return stub_o
  231. -- ---------------------------------------------------------------------------
  232. -- Link
  233. link :: GhcLink -- interactive or batch
  234. -> DynFlags -- dynamic flags
  235. -> Bool -- attempt linking in batch mode?
  236. -> HomePackageTable -- what to link
  237. -> IO SuccessFlag
  238. -- For the moment, in the batch linker, we don't bother to tell doLink
  239. -- which packages to link -- it just tries all that are available.
  240. -- batch_attempt_linking should only be *looked at* in batch mode. It
  241. -- should only be True if the upsweep was successful and someone
  242. -- exports main, i.e., we have good reason to believe that linking
  243. -- will succeed.
  244. link LinkInMemory _ _ _
  245. = if cGhcWithInterpreter == "YES"
  246. then -- Not Linking...(demand linker will do the job)
  247. return Succeeded
  248. else panicBadLink LinkInMemory
  249. link NoLink _ _ _
  250. = return Succeeded
  251. link LinkBinary dflags batch_attempt_linking hpt
  252. = link' dflags batch_attempt_linking hpt
  253. link LinkDynLib dflags batch_attempt_linking hpt
  254. = link' dflags batch_attempt_linking hpt
  255. panicBadLink :: GhcLink -> a
  256. panicBadLink other = panic ("link: GHC not built to link this way: " ++
  257. show other)
  258. link' :: DynFlags -- dynamic flags
  259. -> Bool -- attempt linking in batch mode?
  260. -> HomePackageTable -- what to link
  261. -> IO SuccessFlag
  262. link' dflags batch_attempt_linking hpt
  263. | batch_attempt_linking
  264. = do
  265. let
  266. home_mod_infos = eltsUFM hpt
  267. -- the packages we depend on
  268. pkg_deps = concatMap (map fst . dep_pkgs . mi_deps . hm_iface) home_mod_infos
  269. -- the linkables to link
  270. linkables = map (expectJust "link".hm_linkable) home_mod_infos
  271. debugTraceMsg dflags 3 (text "link: linkables are ..." $$ vcat (map ppr linkables))
  272. -- check for the -no-link flag
  273. if isNoLink (ghcLink dflags)
  274. then do debugTraceMsg dflags 3 (text "link(batch): linking omitted (-c flag given).")
  275. return Succeeded
  276. else do
  277. let getOfiles (LM _ _ us) = map nameOfObject (filter isObject us)
  278. obj_files = concatMap getOfiles linkables
  279. exe_file = exeFileName dflags
  280. linking_needed <- linkingNeeded dflags linkables pkg_deps
  281. if not (gopt Opt_ForceRecomp dflags) && not linking_needed
  282. then do debugTraceMsg dflags 2 (text exe_file <+> ptext (sLit "is up to date, linking not required."))
  283. return Succeeded
  284. else do
  285. compilationProgressMsg dflags ("Linking " ++ exe_file ++ " ...")
  286. -- Don't showPass in Batch mode; doLink will do that for us.
  287. let link = case ghcLink dflags of
  288. LinkBinary -> linkBinary
  289. LinkDynLib -> linkDynLibCheck
  290. other -> panicBadLink other
  291. link dflags obj_files pkg_deps
  292. debugTraceMsg dflags 3 (text "link: done")
  293. -- linkBinary only returns if it succeeds
  294. return Succeeded
  295. | otherwise
  296. = do debugTraceMsg dflags 3 (text "link(batch): upsweep (partially) failed OR" $$
  297. text " Main.main not exported; not linking.")
  298. return Succeeded
  299. linkingNeeded :: DynFlags -> [Linkable] -> [PackageId] -> IO Bool
  300. linkingNeeded dflags linkables pkg_deps = do
  301. -- if the modification time on the executable is later than the
  302. -- modification times on all of the objects and libraries, then omit
  303. -- linking (unless the -fforce-recomp flag was given).
  304. let exe_file = exeFileName dflags
  305. e_exe_time <- tryIO $ getModificationUTCTime exe_file
  306. case e_exe_time of
  307. Left _ -> return True
  308. Right t -> do
  309. -- first check object files and extra_ld_inputs
  310. let extra_ld_inputs = ldInputs dflags
  311. e_extra_times <- mapM (tryIO . getModificationUTCTime) extra_ld_inputs
  312. let (errs,extra_times) = splitEithers e_extra_times
  313. let obj_times = map linkableTime linkables ++ extra_times
  314. if not (null errs) || any (t <) obj_times
  315. then return True
  316. else do
  317. -- next, check libraries. XXX this only checks Haskell libraries,
  318. -- not extra_libraries or -l things from the command line.
  319. let pkg_map = pkgIdMap (pkgState dflags)
  320. pkg_hslibs = [ (libraryDirs c, lib)
  321. | Just c <- map (lookupPackage pkg_map) pkg_deps,
  322. lib <- packageHsLibs dflags c ]
  323. pkg_libfiles <- mapM (uncurry (findHSLib dflags)) pkg_hslibs
  324. if any isNothing pkg_libfiles then return True else do
  325. e_lib_times <- mapM (tryIO . getModificationUTCTime)
  326. (catMaybes pkg_libfiles)
  327. let (lib_errs,lib_times) = splitEithers e_lib_times
  328. if not (null lib_errs) || any (t <) lib_times
  329. then return True
  330. else checkLinkInfo dflags pkg_deps exe_file
  331. -- Returns 'False' if it was, and we can avoid linking, because the
  332. -- previous binary was linked with "the same options".
  333. checkLinkInfo :: DynFlags -> [PackageId] -> FilePath -> IO Bool
  334. checkLinkInfo dflags pkg_deps exe_file
  335. | not (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
  336. -- ToDo: Windows and OS X do not use the ELF binary format, so
  337. -- readelf does not work there. We need to find another way to do
  338. -- this.
  339. = return False -- conservatively we should return True, but not
  340. -- linking in this case was the behaviour for a long
  341. -- time so we leave it as-is.
  342. | otherwise
  343. = do
  344. link_info <- getLinkInfo dflags pkg_deps
  345. debugTraceMsg dflags 3 $ text ("Link info: " ++ link_info)
  346. m_exe_link_info <- readElfSection dflags ghcLinkInfoSectionName exe_file
  347. debugTraceMsg dflags 3 $ text ("Exe link info: " ++ show m_exe_link_info)
  348. return (Just link_info /= m_exe_link_info)
  349. platformSupportsSavingLinkOpts :: OS -> Bool
  350. platformSupportsSavingLinkOpts os
  351. | os == OSSolaris2 = False -- see #5382
  352. | otherwise = osElfTarget os
  353. ghcLinkInfoSectionName :: String
  354. ghcLinkInfoSectionName = ".debug-ghc-link-info"
  355. -- if we use the ".debug" prefix, then strip will strip it by default
  356. findHSLib :: DynFlags -> [String] -> String -> IO (Maybe FilePath)
  357. findHSLib dflags dirs lib = do
  358. let batch_lib_file = if gopt Opt_Static dflags
  359. then "lib" ++ lib <.> "a"
  360. else mkSOName (targetPlatform dflags) lib
  361. found <- filterM doesFileExist (map (</> batch_lib_file) dirs)
  362. case found of
  363. [] -> return Nothing
  364. (x:_) -> return (Just x)
  365. -- -----------------------------------------------------------------------------
  366. -- Compile files in one-shot mode.
  367. oneShot :: HscEnv -> Phase -> [(String, Maybe Phase)] -> IO ()
  368. oneShot hsc_env stop_phase srcs = do
  369. o_files <- mapM (compileFile hsc_env stop_phase) srcs
  370. doLink (hsc_dflags hsc_env) stop_phase o_files
  371. compileFile :: HscEnv -> Phase -> (FilePath, Maybe Phase) -> IO FilePath
  372. compileFile hsc_env stop_phase (src, mb_phase) = do
  373. exists <- doesFileExist src
  374. when (not exists) $
  375. throwGhcExceptionIO (CmdLineError ("does not exist: " ++ src))
  376. let
  377. dflags = hsc_dflags hsc_env
  378. split = gopt Opt_SplitObjs dflags
  379. mb_o_file = outputFile dflags
  380. ghc_link = ghcLink dflags -- Set by -c or -no-link
  381. -- When linking, the -o argument refers to the linker's output.
  382. -- otherwise, we use it as the name for the pipeline's output.
  383. output
  384. -- If we are dong -fno-code, then act as if the output is
  385. -- 'Temporary'. This stops GHC trying to copy files to their
  386. -- final location.
  387. | HscNothing <- hscTarget dflags = Temporary
  388. | StopLn <- stop_phase, not (isNoLink ghc_link) = Persistent
  389. -- -o foo applies to linker
  390. | isJust mb_o_file = SpecificFile
  391. -- -o foo applies to the file we are compiling now
  392. | otherwise = Persistent
  393. stop_phase' = case stop_phase of
  394. As | split -> SplitAs
  395. _ -> stop_phase
  396. ( _, out_file) <- runPipeline stop_phase' hsc_env
  397. (src, fmap RealPhase mb_phase) Nothing output
  398. Nothing{-no ModLocation-} Nothing
  399. return out_file
  400. doLink :: DynFlags -> Phase -> [FilePath] -> IO ()
  401. doLink dflags stop_phase o_files
  402. | not (isStopLn stop_phase)
  403. = return () -- We stopped before the linking phase
  404. | otherwise
  405. = case ghcLink dflags of
  406. NoLink -> return ()
  407. LinkBinary -> linkBinary dflags o_files []
  408. LinkDynLib -> linkDynLibCheck dflags o_files []
  409. other -> panicBadLink other
  410. -- ---------------------------------------------------------------------------
  411. data PipelineOutput
  412. = Temporary
  413. -- ^ Output should be to a temporary file: we're going to
  414. -- run more compilation steps on this output later.
  415. | Persistent
  416. -- ^ We want a persistent file, i.e. a file in the current directory
  417. -- derived from the input filename, but with the appropriate extension.
  418. -- eg. in "ghc -c Foo.hs" the output goes into ./Foo.o.
  419. | SpecificFile
  420. -- ^ The output must go into the specific outputFile in DynFlags.
  421. -- We don't store the filename in the constructor as it changes
  422. -- when doing -dynamic-too.
  423. deriving Show
  424. -- | Run a compilation pipeline, consisting of multiple phases.
  425. --
  426. -- This is the interface to the compilation pipeline, which runs
  427. -- a series of compilation steps on a single source file, specifying
  428. -- at which stage to stop.
  429. --
  430. -- The DynFlags can be modified by phases in the pipeline (eg. by
  431. -- OPTIONS_GHC pragmas), and the changes affect later phases in the
  432. -- pipeline.
  433. runPipeline
  434. :: Phase -- ^ When to stop
  435. -> HscEnv -- ^ Compilation environment
  436. -> (FilePath,Maybe PhasePlus) -- ^ Input filename (and maybe -x suffix)
  437. -> Maybe FilePath -- ^ original basename (if different from ^^^)
  438. -> PipelineOutput -- ^ Output filename
  439. -> Maybe ModLocation -- ^ A ModLocation, if this is a Haskell module
  440. -> Maybe FilePath -- ^ stub object, if we have one
  441. -> IO (DynFlags, FilePath) -- ^ (final flags, output filename)
  442. runPipeline stop_phase hsc_env0 (input_fn, mb_phase)
  443. mb_basename output maybe_loc maybe_stub_o
  444. = do let
  445. dflags0 = hsc_dflags hsc_env0
  446. -- Decide where dump files should go based on the pipeline output
  447. dflags = dflags0 { dumpPrefix = Just (basename ++ ".") }
  448. hsc_env = hsc_env0 {hsc_dflags = dflags}
  449. (input_basename, suffix) = splitExtension input_fn
  450. suffix' = drop 1 suffix -- strip off the .
  451. basename | Just b <- mb_basename = b
  452. | otherwise = input_basename
  453. -- If we were given a -x flag, then use that phase to start from
  454. start_phase = fromMaybe (RealPhase (startPhase suffix')) mb_phase
  455. isHaskell (RealPhase (Unlit _)) = True
  456. isHaskell (RealPhase (Cpp _)) = True
  457. isHaskell (RealPhase (HsPp _)) = True
  458. isHaskell (RealPhase (Hsc _)) = True
  459. isHaskell (HscOut {}) = True
  460. isHaskell _ = False
  461. isHaskellishFile = isHaskell start_phase
  462. env = PipeEnv{ pe_isHaskellishFile = isHaskellishFile,
  463. stop_phase,
  464. src_filename = input_fn,
  465. src_basename = basename,
  466. src_suffix = suffix',
  467. output_spec = output }
  468. -- We want to catch cases of "you can't get there from here" before
  469. -- we start the pipeline, because otherwise it will just run off the
  470. -- end.
  471. --
  472. -- There is a partial ordering on phases, where A < B iff A occurs
  473. -- before B in a normal compilation pipeline.
  474. let happensBefore' = happensBefore dflags
  475. case start_phase of
  476. RealPhase start_phase' ->
  477. when (not (start_phase' `happensBefore'` stop_phase)) $
  478. throwGhcExceptionIO (UsageError
  479. ("cannot compile this file to desired target: "
  480. ++ input_fn))
  481. HscOut {} -> return ()
  482. debugTraceMsg dflags 4 (text "Running the pipeline")
  483. r <- runPipeline' start_phase hsc_env env input_fn
  484. maybe_loc maybe_stub_o
  485. -- If we are compiling a Haskell module, and doing
  486. -- -dynamic-too, but couldn't do the -dynamic-too fast
  487. -- path, then rerun the pipeline for the dyn way
  488. let dflags = extractDynFlags hsc_env
  489. when isHaskellishFile $ whenCannotGenerateDynamicToo dflags $ do
  490. debugTraceMsg dflags 4
  491. (text "Running the pipeline again for -dynamic-too")
  492. let dflags' = doDynamicToo dflags
  493. hsc_env' <- newHscEnv dflags'
  494. _ <- runPipeline' start_phase hsc_env' env input_fn
  495. maybe_loc maybe_stub_o
  496. return ()
  497. return r
  498. runPipeline'
  499. :: PhasePlus -- ^ When to start
  500. -> HscEnv -- ^ Compilation environment
  501. -> PipeEnv
  502. -> FilePath -- ^ Input filename
  503. -> Maybe ModLocation -- ^ A ModLocation, if this is a Haskell module
  504. -> Maybe FilePath -- ^ stub object, if we have one
  505. -> IO (DynFlags, FilePath) -- ^ (final flags, output filename)
  506. runPipeline' start_phase hsc_env env input_fn
  507. maybe_loc maybe_stub_o
  508. = do
  509. -- Execute the pipeline...
  510. let state = PipeState{ hsc_env, maybe_loc, maybe_stub_o = maybe_stub_o }
  511. evalP (pipeLoop start_phase input_fn) env state
  512. -- -----------------------------------------------------------------------------
  513. -- The pipeline uses a monad to carry around various bits of information
  514. -- PipeEnv: invariant information passed down
  515. data PipeEnv = PipeEnv {
  516. pe_isHaskellishFile :: Bool,
  517. stop_phase :: Phase, -- ^ Stop just before this phase
  518. src_filename :: String, -- ^ basename of original input source
  519. src_basename :: String, -- ^ basename of original input source
  520. src_suffix :: String, -- ^ its extension
  521. output_spec :: PipelineOutput -- ^ says where to put the pipeline output
  522. }
  523. -- PipeState: information that might change during a pipeline run
  524. data PipeState = PipeState {
  525. hsc_env :: HscEnv,
  526. -- ^ only the DynFlags change in the HscEnv. The DynFlags change
  527. -- at various points, for example when we read the OPTIONS_GHC
  528. -- pragmas in the Cpp phase.
  529. maybe_loc :: Maybe ModLocation,
  530. -- ^ the ModLocation. This is discovered during compilation,
  531. -- in the Hsc phase where we read the module header.
  532. maybe_stub_o :: Maybe FilePath
  533. -- ^ the stub object. This is set by the Hsc phase if a stub
  534. -- object was created. The stub object will be joined with
  535. -- the main compilation object using "ld -r" at the end.
  536. }
  537. getPipeEnv :: CompPipeline PipeEnv
  538. getPipeEnv = P $ \env state -> return (state, env)
  539. getPipeState :: CompPipeline PipeState
  540. getPipeState = P $ \_env state -> return (state, state)
  541. instance HasDynFlags CompPipeline where
  542. getDynFlags = P $ \_env state -> return (state, hsc_dflags (hsc_env state))
  543. setDynFlags :: DynFlags -> CompPipeline ()
  544. setDynFlags dflags = P $ \_env state ->
  545. return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ())
  546. setModLocation :: ModLocation -> CompPipeline ()
  547. setModLocation loc = P $ \_env state ->
  548. return (state{ maybe_loc = Just loc }, ())
  549. setStubO :: FilePath -> CompPipeline ()
  550. setStubO stub_o = P $ \_env state ->
  551. return (state{ maybe_stub_o = Just stub_o }, ())
  552. newtype CompPipeline a = P { unP :: PipeEnv -> PipeState -> IO (PipeState, a) }
  553. evalP :: CompPipeline a -> PipeEnv -> PipeState -> IO a
  554. evalP f env st = liftM snd $ unP f env st
  555. instance Monad CompPipeline where
  556. return a = P $ \_env state -> return (state, a)
  557. P m >>= k = P $ \env state -> do (state',a) <- m env state
  558. unP (k a) env state'
  559. instance MonadIO CompPipeline where
  560. liftIO m = P $ \_env state -> do a <- m; return (state, a)
  561. phaseOutputFilename :: Phase{-next phase-} -> CompPipeline FilePath
  562. phaseOutputFilename next_phase = do
  563. PipeEnv{stop_phase, src_basename, output_spec} <- getPipeEnv
  564. PipeState{maybe_loc, hsc_env} <- getPipeState
  565. let dflags = hsc_dflags hsc_env
  566. liftIO $ getOutputFilename stop_phase output_spec
  567. src_basename dflags next_phase maybe_loc
  568. -- ---------------------------------------------------------------------------
  569. -- outer pipeline loop
  570. -- | pipeLoop runs phases until we reach the stop phase
  571. pipeLoop :: PhasePlus -> FilePath -> CompPipeline (DynFlags, FilePath)
  572. pipeLoop phase input_fn = do
  573. env <- getPipeEnv
  574. dflags <- getDynFlags
  575. let happensBefore' = happensBefore dflags
  576. stopPhase = stop_phase env
  577. case phase of
  578. RealPhase realPhase | realPhase `eqPhase` stopPhase -- All done
  579. -> -- Sometimes, a compilation phase doesn't actually generate any output
  580. -- (eg. the CPP phase when -fcpp is not turned on). If we end on this
  581. -- stage, but we wanted to keep the output, then we have to explicitly
  582. -- copy the file, remembering to prepend a {-# LINE #-} pragma so that
  583. -- further compilation stages can tell what the original filename was.
  584. case output_spec env of
  585. Temporary ->
  586. return (dflags, input_fn)
  587. output ->
  588. do pst <- getPipeState
  589. final_fn <- liftIO $ getOutputFilename
  590. stopPhase output (src_basename env)
  591. dflags stopPhase (maybe_loc pst)
  592. when (final_fn /= input_fn) $ do
  593. let msg = ("Copying `" ++ input_fn ++"' to `" ++ final_fn ++ "'")
  594. line_prag = Just ("{-# LINE 1 \"" ++ src_filename env ++ "\" #-}\n")
  595. liftIO $ copyWithHeader dflags msg line_prag input_fn final_fn
  596. return (dflags, final_fn)
  597. | not (realPhase `happensBefore'` stopPhase)
  598. -- Something has gone wrong. We'll try to cover all the cases when
  599. -- this could happen, so if we reach here it is a panic.
  600. -- eg. it might happen if the -C flag is used on a source file that
  601. -- has {-# OPTIONS -fasm #-}.
  602. -> panic ("pipeLoop: at phase " ++ show realPhase ++
  603. " but I wanted to stop at phase " ++ show stopPhase)
  604. _
  605. -> do liftIO $ debugTraceMsg dflags 4
  606. (ptext (sLit "Running phase") <+> ppr phase)
  607. (next_phase, output_fn) <- runPhase phase input_fn dflags
  608. r <- pipeLoop next_phase output_fn
  609. case phase of
  610. HscOut {} ->
  611. whenGeneratingDynamicToo dflags $ do
  612. setDynFlags $ doDynamicToo dflags
  613. -- TODO shouldn't ignore result:
  614. _ <- pipeLoop phase input_fn
  615. return ()
  616. _ ->
  617. return ()
  618. return r
  619. -- -----------------------------------------------------------------------------
  620. -- In each phase, we need to know into what filename to generate the
  621. -- output. All the logic about which filenames we generate output
  622. -- into is embodied in the following function.
  623. getOutputFilename
  624. :: Phase -> PipelineOutput -> String
  625. -> DynFlags -> Phase{-next phase-} -> Maybe ModLocation -> IO FilePath
  626. getOutputFilename stop_phase output basename dflags next_phase maybe_location
  627. | is_last_phase, Persistent <- output = persistent_fn
  628. | is_last_phase, SpecificFile <- output = case outputFile dflags of
  629. Just f -> return f
  630. Nothing ->
  631. panic "SpecificFile: No filename"
  632. | keep_this_output = persistent_fn
  633. | otherwise = newTempName dflags suffix
  634. where
  635. hcsuf = hcSuf dflags
  636. odir = objectDir dflags
  637. osuf = objectSuf dflags
  638. keep_hc = gopt Opt_KeepHcFiles dflags
  639. keep_s = gopt Opt_KeepSFiles dflags
  640. keep_bc = gopt Opt_KeepLlvmFiles dflags
  641. myPhaseInputExt HCc = hcsuf
  642. myPhaseInputExt MergeStub = osuf
  643. myPhaseInputExt StopLn = osuf
  644. myPhaseInputExt other = phaseInputExt other
  645. is_last_phase = next_phase `eqPhase` stop_phase
  646. -- sometimes, we keep output from intermediate stages
  647. keep_this_output =
  648. case next_phase of
  649. As | keep_s -> True
  650. LlvmOpt | keep_bc -> True
  651. HCc | keep_hc -> True
  652. _other -> False
  653. suffix = myPhaseInputExt next_phase
  654. -- persistent object files get put in odir
  655. persistent_fn
  656. | StopLn <- next_phase = return odir_persistent
  657. | otherwise = return persistent
  658. persistent = basename <.> suffix
  659. odir_persistent
  660. | Just loc <- maybe_location = ml_obj_file loc
  661. | Just d <- odir = d </> persistent
  662. | otherwise = persistent
  663. data PhasePlus = RealPhase Phase
  664. | HscOut HscSource ModuleName HscStatus
  665. instance Outputable PhasePlus where
  666. ppr (RealPhase p) = ppr p
  667. ppr (HscOut {}) = text "HscOut"
  668. -- -----------------------------------------------------------------------------
  669. -- | Each phase in the pipeline returns the next phase to execute, and the
  670. -- name of the file in which the output was placed.
  671. --
  672. -- We must do things dynamically this way, because we often don't know
  673. -- what the rest of the phases will be until part-way through the
  674. -- compilation: for example, an {-# OPTIONS -fasm #-} at the beginning
  675. -- of a source file can change the latter stages of the pipeline from
  676. -- taking the via-C route to using the native code generator.
  677. --
  678. runPhase :: PhasePlus -- ^ Run this phase
  679. -> FilePath -- ^ name of the input file
  680. -> DynFlags -- ^ for convenience, we pass the current dflags in
  681. -> CompPipeline (PhasePlus, -- next phase to run
  682. FilePath) -- output filename
  683. -- Invariant: the output filename always contains the output
  684. -- Interesting case: Hsc when there is no recompilation to do
  685. -- Then the output filename is still a .o file
  686. -------------------------------------------------------------------------------
  687. -- Unlit phase
  688. runPhase (RealPhase (Unlit sf)) input_fn dflags
  689. = do
  690. output_fn <- phaseOutputFilename (Cpp sf)
  691. let unlit_flags = getOpts dflags opt_L
  692. flags = map SysTools.Option unlit_flags ++
  693. [ -- The -h option passes the file name for unlit to
  694. -- put in a #line directive
  695. SysTools.Option "-h"
  696. , SysTools.Option $ escape $ normalise input_fn
  697. , SysTools.FileOption "" input_fn
  698. , SysTools.FileOption "" output_fn
  699. ]
  700. liftIO $ SysTools.runUnlit dflags flags
  701. return (RealPhase (Cpp sf), output_fn)
  702. where
  703. -- escape the characters \, ", and ', but don't try to escape
  704. -- Unicode or anything else (so we don't use Util.charToC
  705. -- here). If we get this wrong, then in
  706. -- Coverage.addTicksToBinds where we check that the filename in
  707. -- a SrcLoc is the same as the source filenaame, the two will
  708. -- look bogusly different. See test:
  709. -- libraries/hpc/tests/function/subdir/tough2.lhs
  710. escape ('\\':cs) = '\\':'\\': escape cs
  711. escape ('\"':cs) = '\\':'\"': escape cs
  712. escape ('\'':cs) = '\\':'\'': escape cs
  713. escape (c:cs) = c : escape cs
  714. escape [] = []
  715. -------------------------------------------------------------------------------
  716. -- Cpp phase : (a) gets OPTIONS out of file
  717. -- (b) runs cpp if necessary
  718. runPhase (RealPhase (Cpp sf)) input_fn dflags0
  719. = do
  720. src_opts <- liftIO $ getOptionsFromFile dflags0 input_fn
  721. (dflags1, unhandled_flags, warns)
  722. <- liftIO $ parseDynamicFilePragma dflags0 src_opts
  723. setDynFlags dflags1
  724. liftIO $ checkProcessArgsResult dflags1 unhandled_flags
  725. if not (xopt Opt_Cpp dflags1) then do
  726. -- we have to be careful to emit warnings only once.
  727. unless (gopt Opt_Pp dflags1) $
  728. liftIO $ handleFlagWarnings dflags1 warns
  729. -- no need to preprocess CPP, just pass input file along
  730. -- to the next phase of the pipeline.
  731. return (RealPhase (HsPp sf), input_fn)
  732. else do
  733. output_fn <- phaseOutputFilename (HsPp sf)
  734. liftIO $ doCpp dflags1 True{-raw-} False{-no CC opts-}
  735. input_fn output_fn
  736. -- re-read the pragmas now that we've preprocessed the file
  737. -- See #2464,#3457
  738. src_opts <- liftIO $ getOptionsFromFile dflags0 output_fn
  739. (dflags2, unhandled_flags, warns)
  740. <- liftIO $ parseDynamicFilePragma dflags0 src_opts
  741. liftIO $ checkProcessArgsResult dflags2 unhandled_flags
  742. unless (gopt Opt_Pp dflags2) $
  743. liftIO $ handleFlagWarnings dflags2 warns
  744. -- the HsPp pass below will emit warnings
  745. setDynFlags dflags2
  746. return (RealPhase (HsPp sf), output_fn)
  747. -------------------------------------------------------------------------------
  748. -- HsPp phase
  749. runPhase (RealPhase (HsPp sf)) input_fn dflags
  750. = do
  751. if not (gopt Opt_Pp dflags) then
  752. -- no need to preprocess, just pass input file along
  753. -- to the next phase of the pipeline.
  754. return (RealPhase (Hsc sf), input_fn)
  755. else do
  756. let hspp_opts = getOpts dflags opt_F
  757. PipeEnv{src_basename, src_suffix} <- getPipeEnv
  758. let orig_fn = src_basename <.> src_suffix
  759. output_fn <- phaseOutputFilename (Hsc sf)
  760. liftIO $ SysTools.runPp dflags
  761. ( [ SysTools.Option orig_fn
  762. , SysTools.Option input_fn
  763. , SysTools.FileOption "" output_fn
  764. ] ++
  765. map SysTools.Option hspp_opts
  766. )
  767. -- re-read pragmas now that we've parsed the file (see #3674)
  768. src_opts <- liftIO $ getOptionsFromFile dflags output_fn
  769. (dflags1, unhandled_flags, warns)
  770. <- liftIO $ parseDynamicFilePragma dflags src_opts
  771. setDynFlags dflags1
  772. liftIO $ checkProcessArgsResult dflags1 unhandled_flags
  773. liftIO $ handleFlagWarnings dflags1 warns
  774. return (RealPhase (Hsc sf), output_fn)
  775. -----------------------------------------------------------------------------
  776. -- Hsc phase
  777. -- Compilation of a single module, in "legacy" mode (_not_ under
  778. -- the direction of the compilation manager).
  779. runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0
  780. = do -- normal Hsc mode, not mkdependHS
  781. PipeEnv{ stop_phase=stop,
  782. src_basename=basename,
  783. src_suffix=suff } <- getPipeEnv
  784. -- we add the current directory (i.e. the directory in which
  785. -- the .hs files resides) to the include path, since this is
  786. -- what gcc does, and it's probably what you want.
  787. let current_dir = takeDirectory basename
  788. paths = includePaths dflags0
  789. dflags = dflags0 { includePaths = current_dir : paths }
  790. setDynFlags dflags
  791. -- gather the imports and module name
  792. (hspp_buf,mod_name,imps,src_imps) <- liftIO $
  793. case src_flavour of
  794. ExtCoreFile -> do -- no explicit imports in ExtCore input.
  795. m <- getCoreModuleName input_fn
  796. return (Nothing, mkModuleName m, [], [])
  797. _ -> do
  798. buf <- hGetStringBuffer input_fn
  799. (src_imps,imps,L _ mod_name) <- getImports dflags buf input_fn (basename <.> suff)
  800. return (Just buf, mod_name, imps, src_imps)
  801. -- Take -o into account if present
  802. -- Very like -ohi, but we must *only* do this if we aren't linking
  803. -- (If we're linking then the -o applies to the linked thing, not to
  804. -- the object file for one module.)
  805. -- Note the nasty duplication with the same computation in compileFile above
  806. location <- getLocation src_flavour mod_name
  807. let o_file = ml_obj_file location -- The real object file
  808. -- Figure out if the source has changed, for recompilation avoidance.
  809. --
  810. -- Setting source_unchanged to True means that M.o seems
  811. -- to be up to date wrt M.hs; so no need to recompile unless imports have
  812. -- changed (which the compiler itself figures out).
  813. -- Setting source_unchanged to False tells the compiler that M.o is out of
  814. -- date wrt M.hs (or M.o doesn't exist) so we must recompile regardless.
  815. src_timestamp <- liftIO $ getModificationUTCTime (basename <.> suff)
  816. source_unchanged <- liftIO $
  817. if not (isStopLn stop)
  818. -- SourceModified unconditionally if
  819. -- (a) recompilation checker is off, or
  820. -- (b) we aren't going all the way to .o file (e.g. ghc -S)
  821. then return SourceModified
  822. -- Otherwise look at file modification dates
  823. else do o_file_exists <- doesFileExist o_file
  824. if not o_file_exists
  825. then return SourceModified -- Need to recompile
  826. else do t2 <- getModificationUTCTime o_file
  827. if t2 > src_timestamp
  828. then return SourceUnmodified
  829. else return SourceModified
  830. let extCore_filename = basename ++ ".hcr"
  831. PipeState{hsc_env=hsc_env'} <- getPipeState
  832. -- Tell the finder cache about this module
  833. mod <- liftIO $ addHomeModuleToFinder hsc_env' mod_name location
  834. -- Make the ModSummary to hand to hscMain
  835. let
  836. mod_summary = ModSummary { ms_mod = mod,
  837. ms_hsc_src = src_flavour,
  838. ms_hspp_file = input_fn,
  839. ms_hspp_opts = dflags,
  840. ms_hspp_buf = hspp_buf,
  841. ms_location = location,
  842. ms_hs_date = src_timestamp,
  843. ms_obj_date = Nothing,
  844. ms_textual_imps = imps,
  845. ms_srcimps = src_imps }
  846. -- run the compiler!
  847. result <- liftIO $ hscCompileOneShot hsc_env' extCore_filename
  848. mod_summary source_unchanged
  849. return (HscOut src_flavour mod_name result,
  850. panic "HscOut doesn't have an input filename")
  851. runPhase (HscOut src_flavour mod_name result) _ dflags = do
  852. location <- getLocation src_flavour mod_name
  853. setModLocation location
  854. let o_file = ml_obj_file location -- The real object file
  855. hsc_lang = hscTarget dflags
  856. next_phase = hscPostBackendPhase dflags src_flavour hsc_lang
  857. case result of
  858. HscNotGeneratingCode ->
  859. return (RealPhase next_phase,
  860. panic "No output filename from Hsc when no-code")
  861. HscUpToDate ->
  862. do liftIO $ touchObjectFile dflags o_file
  863. -- The .o file must have a later modification date
  864. -- than the source file (else we wouldn't get Nothing)
  865. -- but we touch it anyway, to keep 'make' happy (we think).
  866. return (RealPhase StopLn, o_file)
  867. HscUpdateBoot ->
  868. do -- In the case of hs-boot files, generate a dummy .o-boot
  869. -- stamp file for the benefit of Make
  870. liftIO $ touchObjectFile dflags o_file
  871. return (RealPhase next_phase, o_file)
  872. HscRecomp cgguts mod_summary
  873. -> do output_fn <- phaseOutputFilename next_phase
  874. PipeState{hsc_env=hsc_env'} <- getPipeState
  875. (outputFilename, mStub) <- liftIO $ hscGenHardCode hsc_env' cgguts mod_summary output_fn
  876. case mStub of
  877. Nothing -> return ()
  878. Just stub_c ->
  879. do stub_o <- liftIO $ compileStub hsc_env' stub_c
  880. setStubO stub_o
  881. return (RealPhase next_phase, outputFilename)
  882. -----------------------------------------------------------------------------
  883. -- Cmm phase
  884. runPhase (RealPhase CmmCpp) input_fn dflags
  885. = do
  886. output_fn <- phaseOutputFilename Cmm
  887. liftIO $ doCpp dflags False{-not raw-} True{-include CC opts-}
  888. input_fn output_fn
  889. return (RealPhase Cmm, output_fn)
  890. runPhase (RealPhase Cmm) input_fn dflags
  891. = do
  892. let hsc_lang = hscTarget dflags
  893. let next_phase = hscPostBackendPhase dflags HsSrcFile hsc_lang
  894. output_fn <- phaseOutputFilename next_phase
  895. PipeState{hsc_env} <- getPipeState
  896. liftIO $ hscCompileCmmFile hsc_env input_fn output_fn
  897. return (RealPhase next_phase, output_fn)
  898. -----------------------------------------------------------------------------
  899. -- Cc phase
  900. -- we don't support preprocessing .c files (with -E) now. Doing so introduces
  901. -- way too many hacks, and I can't say I've ever used it anyway.
  902. runPhase (RealPhase cc_phase) input_fn dflags
  903. | any (cc_phase `eqPhase`) [Cc, Ccpp, HCc, Cobjc, Cobjcpp]
  904. = do
  905. let platform = targetPlatform dflags
  906. cc_opts = getOpts dflags opt_c
  907. hcc = cc_phase `eqPhase` HCc
  908. let cmdline_include_paths = includePaths dflags
  909. -- HC files have the dependent packages stamped into them
  910. pkgs <- if hcc then liftIO $ getHCFilePackages input_fn else return []
  911. -- add package include paths even if we're just compiling .c
  912. -- files; this is the Value Add(TM) that using ghc instead of
  913. -- gcc gives you :)
  914. pkg_include_dirs <- liftIO $ getPackageIncludePath dflags pkgs
  915. let include_paths = foldr (\ x xs -> "-I" : x : xs) []
  916. (cmdline_include_paths ++ pkg_include_dirs)
  917. let gcc_extra_viac_flags = extraGccViaCFlags dflags
  918. let pic_c_flags = picCCOpts dflags
  919. let verbFlags = getVerbFlags dflags
  920. -- cc-options are not passed when compiling .hc files. Our
  921. -- hc code doesn't not #include any header files anyway, so these
  922. -- options aren't necessary.
  923. pkg_extra_cc_opts <- liftIO $
  924. if cc_phase `eqPhase` HCc
  925. then return []
  926. else getPackageExtraCcOpts dflags pkgs
  927. framework_paths <-
  928. if platformUsesFrameworks platform
  929. then do pkgFrameworkPaths <- liftIO $ getPackageFrameworkPath dflags pkgs
  930. let cmdlineFrameworkPaths = frameworkPaths dflags
  931. return $ map ("-F"++)
  932. (cmdlineFrameworkPaths ++ pkgFrameworkPaths)
  933. else return []
  934. let split_objs = gopt Opt_SplitObjs dflags
  935. split_opt | hcc && split_objs = [ "-DUSE_SPLIT_MARKERS" ]
  936. | otherwise = [ ]
  937. let cc_opt | optLevel dflags >= 2 = "-O2"
  938. | otherwise = "-O"
  939. -- Decide next phase
  940. let next_phase = As
  941. output_fn <- phaseOutputFilename next_phase
  942. let
  943. more_hcc_opts =
  944. -- on x86 the floating point regs have greater precision
  945. -- than a double, which leads to unpredictable results.
  946. -- By default, we turn this off with -ffloat-store unless
  947. -- the user specified -fexcess-precision.
  948. (if platformArch platform == ArchX86 &&
  949. not (gopt Opt_ExcessPrecision dflags)
  950. then [ "-ffloat-store" ]
  951. else []) ++
  952. -- gcc's -fstrict-aliasing allows two accesses to memory
  953. -- to be considered non-aliasing if they have different types.
  954. -- This interacts badly with the C code we generate, which is
  955. -- very weakly typed, being derived from C--.
  956. ["-fno-strict-aliasing"]
  957. let gcc_lang_opt | cc_phase `eqPhase` Ccpp = "c++"
  958. | cc_phase `eqPhase` Cobjc = "objective-c"
  959. | cc_phase `eqPhase` Cobjcpp = "objective-c++"
  960. | otherwise = "c"
  961. liftIO $ SysTools.runCc dflags (
  962. -- force the C compiler to interpret this file as C when
  963. -- compiling .hc files, by adding the -x c option.
  964. -- Also useful for plain .c files, just in case GHC saw a
  965. -- -x c option.
  966. [ SysTools.Option "-x", SysTools.Option gcc_lang_opt
  967. , SysTools.FileOption "" input_fn
  968. , SysTools.Option "-o"
  969. , SysTools.FileOption "" output_fn
  970. ]
  971. ++ map SysTools.Option (
  972. pic_c_flags
  973. -- Stub files generated for foreign exports references the runIO_closure
  974. -- and runNonIO_closure symbols, which are defined in the base package.
  975. -- These symbols are imported into the stub.c file via RtsAPI.h, and the
  976. -- way we do the import depends on whether we're currently compiling
  977. -- the base package or not.
  978. ++ (if platformOS platform == OSMinGW32 &&
  979. thisPackage dflags == basePackageId
  980. then [ "-DCOMPILING_BASE_PACKAGE" ]
  981. else [])
  982. -- We only support SparcV9 and better because V8 lacks an atomic CAS
  983. -- instruction. Note that the user can still override this
  984. -- (e.g., -mcpu=ultrasparc) as GCC picks the "best" -mcpu flag
  985. -- regardless of the ordering.
  986. --
  987. -- This is a temporary hack. See #2872, commit
  988. -- 5bd3072ac30216a505151601884ac88bf404c9f2
  989. ++ (if platformArch platform == ArchSPARC
  990. then ["-mcpu=v9"]
  991. else [])
  992. -- GCC 4.6+ doesn't like -Wimplicit when compiling C++.
  993. ++ (if (cc_phase /= Ccpp && cc_phase /= Cobjcpp)
  994. then ["-Wimplicit"]
  995. else [])
  996. ++ (if hcc
  997. then gcc_extra_viac_flags ++ more_hcc_opts
  998. else [])
  999. ++ verbFlags
  1000. ++ [ "-S", cc_opt ]
  1001. ++ [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
  1002. ++ framework_paths
  1003. ++ cc_opts
  1004. ++ split_opt
  1005. ++ include_paths
  1006. ++ pkg_extra_cc_opts
  1007. ))
  1008. return (RealPhase next_phase, output_fn)
  1009. -----------------------------------------------------------------------------
  1010. -- Splitting phase
  1011. runPhase (RealPhase Splitter) input_fn dflags
  1012. = do -- tmp_pfx is the prefix used for the split .s files
  1013. split_s_prefix <- liftIO $ SysTools.newTempName dflags "split"
  1014. let n_files_fn = split_s_prefix
  1015. liftIO $ SysTools.runSplit dflags
  1016. [ SysTools.FileOption "" input_fn
  1017. , SysTools.FileOption "" split_s_prefix
  1018. , SysTools.FileOption "" n_files_fn
  1019. ]
  1020. -- Save the number of split files for future references
  1021. s <- liftIO $ readFile n_files_fn
  1022. let n_files = read s :: Int
  1023. dflags' = dflags { splitInfo = Just (split_s_prefix, n_files) }
  1024. setDynFlags dflags'
  1025. -- Remember to delete all these files
  1026. liftIO $ addFilesToClean dflags'
  1027. [ split_s_prefix ++ "__" ++ show n ++ ".s"
  1028. | n <- [1..n_files]]
  1029. return (RealPhase SplitAs,
  1030. "**splitter**") -- we don't use the filename in SplitAs
  1031. -----------------------------------------------------------------------------
  1032. -- As, SpitAs phase : Assembler
  1033. -- This is for calling the assembler on a regular assembly file (not split).
  1034. runPhase (RealPhase As) input_fn dflags
  1035. = do
  1036. -- LLVM from version 3.0 onwards doesn't support the OS X system
  1037. -- assembler, so we use clang as the assembler instead. (#5636)
  1038. let whichAsProg | hscTarget dflags == HscLlvm &&
  1039. platformOS (targetPlatform dflags) == OSDarwin
  1040. = do
  1041. -- be careful what options we call clang with
  1042. -- see #5903 and #7617 for bugs caused by this.
  1043. llvmVer <- liftIO $ figureLlvmVersion dflags
  1044. return $ case llvmVer of
  1045. Just n | n >= 30 -> SysTools.runClang
  1046. _ -> SysTools.runAs
  1047. | otherwise = return SysTools.runAs
  1048. as_prog <- whichAsProg
  1049. let as_opts = getOpts dflags opt_a
  1050. cmdline_include_paths = includePaths dflags
  1051. next_phase <- maybeMergeStub
  1052. output_fn <- phaseOutputFilename next_phase
  1053. -- we create directories for the object file, because it
  1054. -- might be a hierarchical module.
  1055. liftIO $ createDirectoryIfMissing True (takeDirectory output_fn)
  1056. let runAssembler inputFilename outputFilename
  1057. = liftIO $ as_prog dflags
  1058. (map SysTools.Option as_opts
  1059. ++ [ SysTools.Option ("-I" ++ p) | p <- cmdline_include_paths ]
  1060. -- We only support SparcV9 and better because V8 lacks an atomic CAS
  1061. -- instruction so we have to make sure that the assembler accepts the
  1062. -- instruction set. Note that the user can still override this
  1063. -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
  1064. -- regardless of the ordering.
  1065. --
  1066. -- This is a temporary hack.
  1067. ++ (if platformArch (targetPlatform dflags) == ArchSPARC
  1068. then [SysTools.Option "-mcpu=v9"]
  1069. else [])
  1070. ++ [ SysTools.Option "-x", SysTools.Option "assembler-with-cpp"
  1071. , SysTools.Option "-c"
  1072. , SysTools.FileOption "" inputFilename
  1073. , SysTools.Option "-o"
  1074. , SysTools.FileOption "" outputFilename
  1075. ])
  1076. liftIO $ debugTraceMsg dflags 4 (text "Running the assembler")
  1077. runAssembler input_fn output_fn
  1078. return (RealPhase next_phase, output_fn)
  1079. -- This is for calling the assembler on a split assembly file (so a collection
  1080. -- of assembly files)
  1081. runPhase (RealPhase SplitAs) _input_fn dflags
  1082. = do
  1083. -- we'll handle the stub_o file in this phase, so don't MergeStub,
  1084. -- just jump straight to StopLn afterwards.
  1085. let next_phase = StopLn
  1086. output_fn <- phaseOutputFilename next_phase
  1087. let base_o = dropExtension output_fn
  1088. osuf = objectSuf dflags
  1089. split_odir = base_o ++ "_" ++ osuf ++ "_split"
  1090. liftIO $ createDirectoryIfMissing True split_odir
  1091. -- remove M_split/ *.o, because we're going to archive M_split/ *.o
  1092. -- later and we don't want to pick up any old objects.
  1093. fs <- liftIO $ getDirectoryContents split_odir
  1094. liftIO $ mapM_ removeFile $
  1095. map (split_odir </>) $ filter (osuf `isSuffixOf`) fs
  1096. let as_opts = getOpts dflags opt_a
  1097. let (split_s_prefix, n) = case splitInfo dflags of
  1098. Nothing -> panic "No split info"
  1099. Just x -> x
  1100. let split_s n = split_s_prefix ++ "__" ++ show n <.> "s"
  1101. split_obj :: Int -> FilePath
  1102. split_obj n = split_odir </>
  1103. takeFileName base_o ++ "__" ++ show n <.> osuf
  1104. let assemble_file n
  1105. = SysTools.runAs dflags
  1106. (map SysTools.Option as_opts ++
  1107. -- We only support SparcV9 and better because V8 lacks an atomic CAS
  1108. -- instruction so we have to make sure that the assembler accepts the
  1109. -- instruction set. Note that the user can still override this
  1110. -- (e.g., -mcpu=ultrasparc). GCC picks the "best" -mcpu flag
  1111. -- regardless of the ordering.
  1112. --
  1113. -- This is a temporary hack.
  1114. (if platformArch (targetPlatform dflags) == ArchSPARC
  1115. then [SysTools.Option "-mcpu=v9"]
  1116. else []) ++
  1117. [ SysTools.Option "-c"
  1118. , SysTools.Option "-o"
  1119. , SysTools.FileOption "" (split_obj n)
  1120. , SysTools.FileOption "" (split_s n)
  1121. ])
  1122. liftIO $ mapM_ assemble_file [1..n]
  1123. -- Note [pipeline-split-init]
  1124. -- If we have a stub file, it may contain constructor
  1125. -- functions for initialisation of this module. We can't
  1126. -- simply leave the stub as a separate object file, because it
  1127. -- will never be linked in: nothing refers to it. We need to
  1128. -- ensure that if we ever refer to the data in this module
  1129. -- that needs initialisation, then we also pull in the
  1130. -- initialisation routine.
  1131. --
  1132. -- To that end, we make a DANGEROUS ASSUMPTION here: the data
  1133. -- that needs to be initialised is all in the FIRST split
  1134. -- object. See Note [codegen-split-init].
  1135. PipeState{maybe_stub_o} <- getPipeState
  1136. case maybe_stub_o of
  1137. Nothing -> return ()
  1138. Just stub_o -> liftIO $ do
  1139. tmp_split_1 <- newTempName dflags osuf
  1140. let split_1 = split_obj 1
  1141. copyFile split_1 tmp_split_1
  1142. removeFile split_1
  1143. joinObjectFiles dflags [tmp_split_1, stub_o] split_1
  1144. -- join them into a single .o file
  1145. liftIO $ joinObjectFiles dflags (map split_obj [1..n]) output_fn
  1146. return (RealPhase next_phase, output_fn)
  1147. -----------------------------------------------------------------------------
  1148. -- LlvmOpt phase
  1149. runPhase (RealPhase LlvmOpt) input_fn dflags
  1150. = do
  1151. ver <- liftIO $ readIORef (llvmVersion dflags)
  1152. let lo_opts = getOpts dflags opt_lo
  1153. opt_lvl = max 0 (min 2 $ optLevel dflags)
  1154. -- don't specify anything if user has specified commands. We do this
  1155. -- for opt but not llc since opt is very specifically for optimisation
  1156. -- passes only, so if the user is passing us extra options we assume
  1157. -- they know what they are doing and don't get in the way.
  1158. optFlag = if null lo_opts
  1159. then [SysTools.Option (llvmOpts !! opt_lvl)]
  1160. else []
  1161. tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier
  1162. | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
  1163. | otherwise = "--enable-tbaa=false"
  1164. output_fn <- phaseOutputFilename LlvmLlc
  1165. liftIO $ SysTools.runLlvmOpt dflags
  1166. ([ SysTools.FileOption "" input_fn,
  1167. SysTools.Option "-o",
  1168. SysTools.FileOption "" output_fn]
  1169. ++ optFlag
  1170. ++ [SysTools.Option tbaa]
  1171. ++ map SysTools.Option lo_opts)
  1172. return (RealPhase LlvmLlc, output_fn)
  1173. where
  1174. -- we always (unless -optlo specified) run Opt since we rely on it to
  1175. -- fix up some pretty big deficiencies in the code we generate
  1176. llvmOpts = ["-mem2reg", "-O1", "-O2"]
  1177. -----------------------------------------------------------------------------
  1178. -- LlvmLlc phase
  1179. runPhase (RealPhase LlvmLlc) input_fn dflags
  1180. = do
  1181. ver <- liftIO $ readIORef (llvmVersion dflags)
  1182. let lc_opts = getOpts dflags opt_lc
  1183. opt_lvl = max 0 (min 2 $ optLevel dflags)
  1184. -- iOS requires external references to be loaded indirectly from the
  1185. -- DATA segment or dyld traps at runtime writing into TEXT: see #7722
  1186. rmodel | platformOS (targetPlatform dflags) == OSiOS = "dynamic-no-pic"
  1187. | gopt Opt_PIC dflags = "pic"
  1188. | not (gopt Opt_Static dflags) = "dynamic-no-pic"
  1189. | otherwise = "static"
  1190. tbaa | ver < 29 = "" -- no tbaa in 2.8 and earlier
  1191. | gopt Opt_LlvmTBAA dflags = "--enable-tbaa=true"
  1192. | otherwise = "--enable-tbaa=false"
  1193. -- hidden debugging flag '-dno-llvm-mangler' to skip mangling
  1194. let next_phase = case gopt Opt_NoLlvmMangler dflags of
  1195. False -> LlvmMangle
  1196. True | gopt Opt_SplitObjs dflags -> Splitter
  1197. True -> As
  1198. output_fn <- phaseOutputFilename next_phase
  1199. liftIO $ SysTools.runLlvmLlc dflags
  1200. ([ SysTools.Option (llvmOpts !! opt_lvl),
  1201. SysTools.Option $ "-relocation-model=" ++ rmodel,
  1202. SysTools.FileOption "" input_fn,
  1203. SysTools.Option "-o", SysTools.FileOption "" output_fn]
  1204. ++ map SysTools.Option lc_opts
  1205. ++ [SysTools.Option tbaa]
  1206. ++ map SysTools.Option fpOpts
  1207. ++ map SysTools.Option abiOpts
  1208. ++ map SysTools.Option sseOpts)
  1209. return (RealPhase next_phase, output_fn)
  1210. where
  1211. -- Bug in LLVM at O3 on OSX.
  1212. llvmOpts = if platformOS (targetPlatform dflags) == OSDarwin
  1213. then ["-O1", "-O2", "-O2"]
  1214. else ["-O1", "-O2", "-O3"]
  1215. -- On ARMv7 using LLVM, LLVM fails to allocate floating point registers
  1216. -- while compiling GHC source code. It's probably due to fact that it
  1217. -- does not enable VFP by default. Let's do this manually here
  1218. fpOpts = case platformArch (targetPlatform dflags) of
  1219. ArchARM ARMv7 ext _ -> if (elem VFPv3 ext)
  1220. then ["-mattr=+v7,+vfp3"]
  1221. else if (elem VFPv3D16 ext)
  1222. then ["-mattr=+v7,+vfp3,+d16"]
  1223. else []
  1224. ArchARM ARMv6 ext _ -> if (elem VFPv2 ext)
  1225. then ["-mattr=+v6,+vfp2"]
  1226. else ["-mattr=+v6"]
  1227. _ -> []
  1228. -- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still
  1229. -- compiles into soft-float ABI. We need to explicitly set abi
  1230. -- to hard
  1231. abiOpts = case platformArch (targetPlatform dflags) of
  1232. ArchARM _ _ HARD -> ["-float-abi=hard"]
  1233. ArchARM _ _ _ -> []
  1234. _ -> []
  1235. sseOpts | isSse4_2Enabled dflags = ["-mattr=+sse42"]
  1236. | isSse2Enabled dflags = ["-mattr=+sse2"]
  1237. | otherwise = []
  1238. -----------------------------------------------------------------------------
  1239. -- LlvmMangle phase
  1240. runPhase (RealPhase LlvmMangle) input_fn dflags
  1241. = do
  1242. let next_phase = if gopt Opt_SplitObjs dflags then Splitter else As
  1243. output_fn <- phaseOutputFilename next_phase
  1244. liftIO $ llvmFixupAsm dflags input_fn output_fn
  1245. return (RealPhase next_phase, output_fn)
  1246. -----------------------------------------------------------------------------
  1247. -- merge in stub objects
  1248. runPhase (RealPhase MergeStub) input_fn dflags
  1249. = do
  1250. PipeState{maybe_stub_o} <- getPipeState
  1251. output_fn <- phaseOutputFilename StopLn
  1252. case maybe_stub_o of
  1253. Nothing ->
  1254. panic "runPhase(MergeStub): no stub"
  1255. Just stub_o -> do
  1256. liftIO $ joinObjectFiles dflags [input_fn, stub_o] output_fn
  1257. return (RealPhase StopLn, output_fn)
  1258. -- warning suppression
  1259. runPhase (RealPhase other) _input_fn _dflags =
  1260. panic ("runPhase: don't know how to run phase " ++ show other)
  1261. maybeMergeStub :: CompPipeline Phase
  1262. maybeMergeStub
  1263. = do
  1264. PipeState{maybe_stub_o} <- getPipeState
  1265. if isJust maybe_stub_o then return MergeStub else return StopLn
  1266. getLocation :: HscSource -> ModuleName -> CompPipeline ModLocation
  1267. getLocation src_flavour mod_name = do
  1268. dflags <- getDynFlags
  1269. PipeEnv{ src_basename=basename,
  1270. src_suffix=suff } <- getPipeEnv
  1271. -- Build a ModLocation to pass to hscMain.
  1272. -- The source filename is rather irrelevant by now, but it's used
  1273. -- by hscMain for messages. hscMain also needs
  1274. -- the .hi and .o filenames, and this is as good a way
  1275. -- as any to generate them, and better than most. (e.g. takes
  1276. -- into account the -osuf flags)
  1277. location1 <- liftIO $ mkHomeModLocation2 dflags mod_name basename suff
  1278. -- Boot-ify it if necessary
  1279. let location2 | isHsBoot src_flavour = addBootSuffixLocn location1
  1280. | otherwise = location1
  1281. -- Take -ohi into account if present
  1282. -- This can't be done in mkHomeModuleLocation because
  1283. -- it only applies to the module being compiles
  1284. let ohi = outputHi dflags
  1285. location3 | Just fn <- ohi = location2{ ml_hi_file = fn }
  1286. | otherwise = location2
  1287. -- Take -o into account if present
  1288. -- Very like -ohi, but we must *only* do this if we aren't linking
  1289. -- (If we're linking then the -o applies to the linked thing, not to
  1290. -- the object file for one module.)
  1291. -- Note the nasty duplication with the same computation in compileFile above
  1292. let expl_o_file = outputFile dflags
  1293. location4 | Just ofile <- expl_o_file
  1294. , isNoLink (ghcLink dflags)
  1295. = location3 { ml_obj_file = ofile }
  1296. | otherwise = location3
  1297. return location4
  1298. -----------------------------------------------------------------------------
  1299. -- MoveBinary sort-of-phase
  1300. -- After having produced a binary, move it somewhere else and generate a
  1301. -- wrapper script calling the binary. Currently, we need this only in
  1302. -- a parallel way (i.e. in GUM), because PVM expects the binary in a
  1303. -- central directory.
  1304. -- This is called from linkBinary below, after linking. I haven't made it
  1305. -- a separate phase to minimise interfering with other modules, and
  1306. -- we don't need the generality of a phase (MoveBinary is always
  1307. -- done after linking and makes only sense in a parallel setup) -- HWL
  1308. runPhase_MoveBinary :: DynFlags -> FilePath -> IO Bool
  1309. runPhase_MoveBinary dflags input_fn
  1310. | WayPar `elem` ways dflags && not (gopt Opt_Static dflags) =
  1311. panic ("Don't know how to combine PVM wrapper and dynamic wrapper")
  1312. | WayPar `elem` ways dflags = do
  1313. let sysMan = pgm_sysman dflags
  1314. pvm_root <- getEnv "PVM_ROOT"
  1315. pvm_arch <- getEnv "PVM_ARCH"
  1316. let
  1317. pvm_executable_base = "=" ++ input_fn
  1318. pvm_executable = pvm_root ++ "/bin/" ++ pvm_arch ++ "/" ++ pvm_executable_base
  1319. -- nuke old binary; maybe use configur'ed names for cp and rm?
  1320. _ <- tryIO (removeFile pvm_executable)
  1321. -- move the newly created binary into PVM land
  1322. copy dflags "copying PVM executable" input_fn pvm_executable
  1323. -- generate a wrapper script for running a parallel prg under PVM
  1324. writeFile input_fn (mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan)
  1325. return True
  1326. | otherwise = return True
  1327. mkExtraObj :: DynFlags -> Suffix -> String -> IO FilePath
  1328. mkExtraObj dflags extn xs
  1329. = do cFile <- newTempName dflags extn
  1330. oFile <- newTempName dflags "o"
  1331. writeFile cFile xs
  1332. let rtsDetails = getPackageDetails (pkgState dflags) rtsPackageId
  1333. SysTools.runCc dflags
  1334. ([Option "-c",
  1335. FileOption "" cFile,
  1336. Option "-o",
  1337. FileOption "" oFile]
  1338. ++ map SysTools.Option (getOpts dflags opt_c) -- see #5528
  1339. ++ map (FileOption "-I") (includeDirs rtsDetails))
  1340. return oFile
  1341. -- When linking a binary, we need to create a C main() function that
  1342. -- starts everything off. This used to be compiled statically as part
  1343. -- of the RTS, but that made it hard to change the -rtsopts setting,
  1344. -- so now we generate and compile a main() stub as part of every
  1345. -- binary and pass the -rtsopts setting directly to the RTS (#5373)
  1346. --
  1347. mkExtraObjToLinkIntoBinary :: DynFlags -> IO FilePath
  1348. mkExtraObjToLinkIntoBinary dflags = do
  1349. when (gopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $ do
  1350. log_action dflags dflags SevInfo noSrcSpan defaultUserStyle
  1351. (text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
  1352. text " Call hs_init_ghc() from your main() function to set these options.")
  1353. mkExtraObj dflags "c" (showSDoc dflags main)
  1354. where
  1355. main
  1356. | gopt Opt_NoHsMain dflags = empty
  1357. | otherwise = vcat [
  1358. ptext (sLit "#include \"Rts.h\""),
  1359. ptext (sLit "extern StgClosure ZCMain_main_closure;"),
  1360. ptext (sLit "int main(int argc, char *argv[])"),
  1361. char '{',
  1362. ptext (sLit " RtsConfig __conf = defaultRtsConfig;"),
  1363. ptext (sLit " __conf.rts_opts_enabled = ")
  1364. <> text (show (rtsOptsEnabled dflags)) <> semi,
  1365. case rtsOpts dflags of
  1366. Nothing -> empty
  1367. Just opts -> ptext (sLit " __conf.rts_opts= ") <>
  1368. text (show opts) <> semi,
  1369. ptext (sLit " return hs_main(argc, argv, &ZCMain_main_closure,__conf);"),
  1370. char '}',
  1371. char '\n' -- final newline, to keep gcc happy
  1372. ]
  1373. -- Write out the link info section into a new assembly file. Previously
  1374. -- this was included as inline assembly in the main.c file but this
  1375. -- is pretty fragile. gas gets upset trying to calculate relative offsets
  1376. -- that span the .note section (notably .text) when debug info is present
  1377. mkNoteObjsToLinkIntoBinary :: DynFlags -> [PackageId] -> IO [FilePath]
  1378. mkNoteObjsToLinkIntoBinary dflags dep_packages = do
  1379. link_info <- getLinkInfo dflags dep_packages
  1380. if (platformSupportsSavingLinkOpts (platformOS (targetPlatform dflags)))
  1381. then fmap (:[]) $ mkExtraObj dflags "s" (showSDoc dflags (link_opts link_info))
  1382. else return []
  1383. where
  1384. link_opts info = hcat [
  1385. text "\t.section ", text ghcLinkInfoSectionName,
  1386. text ",\"\",",
  1387. text elfSectionNote,
  1388. text "\n",
  1389. text "\t.ascii \"", info', text "\"\n" ]
  1390. where
  1391. info' = text $ escape info
  1392. escape :: String -> String
  1393. escape = concatMap (charToC.fromIntegral.ord)
  1394. elfSectionNote :: String
  1395. elfSectionNote = case platformArch (targetPlatform dflags) of
  1396. ArchARM _ _ _ -> "%note"
  1397. _ -> "@note"
  1398. -- The "link info" is a string representing the parameters of the
  1399. -- link. We save this information in the binary, and the next time we
  1400. -- link, if nothing else has changed, we use the link info stored in
  1401. -- the existing binary to decide whether to re-link or not.
  1402. getLinkInfo :: DynFlags -> [PackageId] -> IO String
  1403. getLinkInfo dflags dep_packages = do
  1404. package_link_opts <- getPackageLinkOpts dflags dep_packages
  1405. pkg_frameworks <- if platformUsesFrameworks (targetPlatform dflags)
  1406. then getPackageFrameworks dflags dep_packages
  1407. else return []
  1408. let extra_ld_inputs = ldInputs dflags
  1409. let
  1410. link_info = (package_link_opts,
  1411. pkg_frameworks,
  1412. rtsOpts dflags,
  1413. rtsOptsEnabled dflags,
  1414. gopt Opt_NoHsMain dflags,
  1415. extra_ld_inputs,
  1416. getOpts dflags opt_l)
  1417. --
  1418. return (show link_info)
  1419. -- generates a Perl skript starting a parallel prg under PVM
  1420. mk_pvm_wrapper_script :: String -> String -> String -> String
  1421. mk_pvm_wrapper_script pvm_executable pvm_executable_base sysMan = unlines $
  1422. [
  1423. "eval 'exec perl -S $0 ${1+\"$@\"}'",
  1424. " if $running_under_some_shell;",
  1425. "# =!=!=!=!=!=!=!=!=!=!=!",
  1426. "# This script is automatically generated: DO NOT EDIT!!!",
  1427. "# Generated by Glasgow Haskell Compiler",
  1428. "# ngoqvam choHbogh vaj' vIHoHnISbej !!!!",
  1429. "#",
  1430. "$pvm_executable = '" ++ pvm_executable ++ "';",
  1431. "$pvm_executable_base = '" ++ pvm_executable_base ++ "';",
  1432. "$SysMan = '" ++ sysMan ++ "';",
  1433. "",
  1434. {- ToDo: add the magical shortcuts again iff we actually use them -- HWL
  1435. "# first, some magical shortcuts to run "commands" on the binary",
  1436. "# (which is hidden)",
  1437. "if ($#ARGV == 1 && $ARGV[0] eq '+RTS' && $ARGV[1] =~ /^--((size|file|strip|rm|nm).*)/ ) {",
  1438. " local($cmd) = $1;",
  1439. " system("$cmd $pvm_executable");",
  1440. " exit(0); # all done",
  1441. "}", -}
  1442. "",
  1443. "# Now, run the real binary; process the args first",
  1444. "$ENV{'PE'} = $pvm_executable_base;", -- ++ pvm_executable_base,
  1445. "$debug = '';",
  1446. "$nprocessors = 0; # the default: as many PEs as machines in PVM config",
  1447. "@nonPVM_args = ();",
  1448. "$in_RTS_args = 0;",
  1449. "",
  1450. "args: while ($a = shift(@ARGV)) {",
  1451. " if ( $a eq '+RTS' ) {",
  1452. " $in_RTS_args = 1;",
  1453. " } elsif ( $a eq '-RTS' ) {",
  1454. " $in_RTS_args = 0;",
  1455. " }",
  1456. " if ( $a eq '-d' && $in_RTS_args ) {",
  1457. " $debug = '-';",
  1458. " } elsif ( $a =~ /^-qN(\\d+)/ && $in_RTS_args ) {",
  1459. " $nprocessors = $1;",
  1460. " } elsif ( $a =~ /^-qp(\\d+)/ && $in_RTS_args ) {",
  1461. " $nprocessors = $1;",
  1462. " } else {",
  1463. " push(@nonPVM_args, $a);",
  1464. " }",
  1465. "}",
  1466. "",
  1467. "local($return_val) = 0;",
  1468. "# Start the parallel execution by calling SysMan",
  1469. "system(\"$SysMan $debug $pvm_executable $nprocessors @nonPVM_args\");",
  1470. "$return_val = $?;",
  1471. "# ToDo: fix race condition moving files and flushing them!!",
  1472. "system(\"cp $ENV{'HOME'}/$pvm_executable_base.???.gr .\") if -f \"$ENV{'HOME'}/$pvm_executable_base.002.gr\";",
  1473. "exit($return_val);"
  1474. ]
  1475. -----------------------------------------------------------------------------
  1476. -- Look for the /* GHC_PACKAGES ... */ comment at the top of a .hc file
  1477. getHCFilePackages :: FilePath -> IO [PackageId]
  1478. getHCFilePackages filename =
  1479. Exception.bracket (openFile filename ReadMode) hClose $ \h -> do
  1480. l <- hGetLine h
  1481. case l of
  1482. '/':'*':' ':'G':'H':'C':'_':'P':'A':'C':'K':'A':'G':'E':'S':rest ->
  1483. return (map stringToPackageId (words rest))
  1484. _other ->
  1485. return []
  1486. -----------------------------------------------------------------------------
  1487. -- Static linking, of .o files
  1488. -- The list of packages passed to link is the list of packages on
  1489. -- which this program depends, as discovered by the compilation
  1490. -- manager. It is combined with the list of packages that the user
  1491. -- specifies on the command line with -package flags.
  1492. --
  1493. -- In one-shot linking mode, we can't discover the package
  1494. -- dependencies (because we haven't actually done any compilation or
  1495. -- read any interface files), so the user must explicitly specify all
  1496. -- the packages.
  1497. linkBinary :: DynFlags -> [FilePath] -> [PackageId] -> IO ()
  1498. linkBinary dflags o_files dep_packages = do
  1499. let platform = targetPlatform dflags
  1500. mySettings = settings dflags
  1501. verbFlags = getVerbFlags dflags
  1502. output_fn = exeFileName dflags
  1503. -- get the full list of packages to link with, by combining the
  1504. -- explicit packages with the auto packages and all of their
  1505. -- dependencies, and eliminating duplicates.
  1506. full_output_fn <- if isAbsolute output_fn
  1507. then return output_fn
  1508. else do d <- getCurrentDirectory
  1509. return $ normalise (d </> output_fn)
  1510. pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
  1511. let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
  1512. get_pkg_lib_path_opts l
  1513. | osElfTarget (platformOS platform) &&
  1514. dynLibLoader dflags == SystemDependent &&
  1515. not (gopt Opt_Static dflags)
  1516. = let libpath = if gopt Opt_RelativeDynlibPaths dflags
  1517. then "$ORIGIN" </>
  1518. (l `makeRelativeTo` full_output_fn)
  1519. else l
  1520. rpath = if gopt Opt_RPath dflags
  1521. then ["-Wl,-rpath", "-Wl," ++ libpath]
  1522. else []
  1523. -- Solaris 11's linker does not support -rpath-link option. It silently
  1524. -- ignores it and then complains about next option which is -l<some
  1525. -- dir> as being a directory and not expected object file, E.g
  1526. -- ld: elf error: file
  1527. -- /tmp/ghc-src/libraries/base/dist-install/build:
  1528. -- elf_begin: I/O error: region read: Is a directory
  1529. rpathlink = if (platformOS platform) == OSSolaris2
  1530. then []
  1531. else ["-Wl,-rpath-link", "-Wl," ++ l]
  1532. in ["-L" ++ l] ++ rpathlink ++ rpath
  1533. | otherwise = ["-L" ++ l]
  1534. let lib_paths = libraryPaths dflags
  1535. let lib_path_opts = map ("-L"++) lib_paths
  1536. extraLinkObj <- mkExtraObjToLinkIntoBinary dflags
  1537. noteLinkObjs <- mkNoteObjsToLinkIntoBinary dflags dep_packages
  1538. pkg_link_opts <- if platformBinariesAreStaticLibs platform
  1539. then -- If building an executable really means
  1540. -- making a static library (e.g. iOS), then
  1541. -- we don't want the options (like -lm)
  1542. -- that getPackageLinkOpts gives us. #7720
  1543. return []
  1544. else getPackageLinkOpts dflags dep_packages
  1545. pkg_framework_path_opts <-
  1546. if platformUsesFrameworks platform
  1547. then do pkg_framework_paths <- getPackageFrameworkPath dflags dep_packages
  1548. return $ map ("-F" ++) pkg_framework_paths
  1549. else return []
  1550. framework_path_opts <-
  1551. if platformUsesFrameworks platform
  1552. then do let framework_paths = frameworkPaths dflags
  1553. return $ map ("-F" ++) framework_paths
  1554. else return []
  1555. pkg_framework_opts <-
  1556. if platformUsesFrameworks platform
  1557. then do pkg_frameworks <- getPackageFrameworks dflags dep_packages
  1558. return $ concat [ ["-framework", fw] | fw <- pkg_frameworks ]
  1559. else return []
  1560. framework_opts <-
  1561. if platformUsesFrameworks platform
  1562. then do let frameworks = cmdlineFrameworks dflags
  1563. -- reverse because they're added in reverse order from
  1564. -- the cmd line:
  1565. return $ concat [ ["-framework", fw]
  1566. | fw <- reverse frameworks ]
  1567. else return []
  1568. -- probably _stub.o files
  1569. let extra_ld_inputs = ldInputs dflags
  1570. -- opts from -optl-<blah> (including -l<blah> options)
  1571. let extra_ld_opts = getOpts dflags opt_l
  1572. -- Here are some libs that need to be linked at the *end* of
  1573. -- the command line, because they contain symbols that are referred to
  1574. -- by the RTS. We can't therefore use the ordinary way opts for these.
  1575. let
  1576. debug_opts | WayDebug `elem` ways dflags = [
  1577. #if defined(HAVE_LIBBFD)
  1578. "-lbfd", "-liberty"
  1579. #endif
  1580. ]
  1581. | otherwise = []
  1582. let thread_opts
  1583. | WayThreaded `elem` ways dflags =
  1584. let os = platformOS (targetPlatform dflags)
  1585. in if os == OSOsf3 then ["-lpthread", "-lexc"]
  1586. else if os `elem` [OSMinGW32, OSFreeBSD, OSOpenBSD,
  1587. OSNetBSD, OSHaiku, OSQNXNTO]
  1588. then []
  1589. else ["-lpthread"]
  1590. | otherwise = []
  1591. rc_objs <- maybeCreateManifest dflags output_fn
  1592. SysTools.runLink dflags (
  1593. map SysTools.Option verbFlags
  1594. ++ [ SysTools.Option "-o"
  1595. , SysTools.FileOption "" output_fn
  1596. ]
  1597. ++ map SysTools.Option (
  1598. []
  1599. -- Permit the linker to auto link _symbol to _imp_symbol.
  1600. -- This lets us link against DLLs without needing an "import library".
  1601. ++ (if platformOS platform == OSMinGW32
  1602. then ["-Wl,--enable-auto-import"]
  1603. else [])
  1604. -- '-no_compact_unwind'
  1605. -- C++/Objective-C exceptions cannot use optimised
  1606. -- stack unwinding code. The optimised form is the
  1607. -- default in Xcode 4 on at least x86_64, and
  1608. -- without this flag we're also seeing warnings
  1609. -- like
  1610. -- ld: warning: could not create compact unwind for .LFB3: non-standard register 5 being saved in prolog
  1611. -- on x86.
  1612. ++ (if sLdSupportsCompactUnwind mySettings &&
  1613. platformOS platform == OSDarwin &&
  1614. platformArch platform `elem` [ArchX86, ArchX86_64]
  1615. then ["-Wl,-no_compact_unwind"]
  1616. else [])
  1617. -- '-Wl,-read_only_relocs,suppress'
  1618. -- ld gives loads of warnings like:
  1619. -- ld: warning: text reloc in _base_GHCziArr_unsafeArray_info to _base_GHCziArr_unsafeArray_closure
  1620. -- when linking any program. We're not sure
  1621. -- whether this is something we ought to fix, but
  1622. -- for now this flags silences them.
  1623. ++ (if platformOS platform == OSDarwin &&
  1624. platformArch platform == ArchX86
  1625. then ["-Wl,-read_only_relocs,suppress"]
  1626. else [])
  1627. ++ o_files
  1628. ++ extra_ld_inputs
  1629. ++ lib_path_opts
  1630. ++ extra_ld_opts
  1631. ++ rc_objs
  1632. ++ framework_path_opts
  1633. ++ framework_opts
  1634. ++ pkg_lib_path_opts
  1635. ++ extraLinkObj:noteLinkObjs
  1636. ++ pkg_link_opts
  1637. ++ pkg_framework_path_opts
  1638. ++ pkg_framework_opts
  1639. ++ debug_opts
  1640. ++ thread_opts
  1641. ))
  1642. -- parallel only: move binary to another dir -- HWL
  1643. success <- runPhase_MoveBinary dflags output_fn
  1644. unless success $
  1645. throwGhcExceptionIO (InstallationError ("cannot move binary"))
  1646. exeFileName :: DynFlags -> FilePath
  1647. exeFileName dflags
  1648. | Just s <- outputFile dflags =
  1649. if platformOS (targetPlatform dflags) == OSMinGW32
  1650. then if null (takeExtension s)
  1651. then s <.> "exe"
  1652. else s
  1653. else s
  1654. | otherwise =
  1655. if platformOS (targetPlatform dflags) == OSMinGW32
  1656. then "main.exe"
  1657. else "a.out"
  1658. maybeCreateManifest
  1659. :: DynFlags
  1660. -> FilePath -- filename of executable
  1661. -> IO [FilePath] -- extra objects to embed, maybe
  1662. maybeCreateManifest dflags exe_filename
  1663. | platformOS (targetPlatform dflags) == OSMinGW32 &&
  1664. gopt Opt_GenManifest dflags
  1665. = do let manifest_filename = exe_filename <.> "manifest"
  1666. writeFile manifest_filename $
  1667. "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n"++
  1668. " <assembly xmlns=\"urn:schemas-microsoft-com:asm.v1\" manifestVersion=\"1.0\">\n"++
  1669. " <assemblyIdentity version=\"1.0.0.0\"\n"++
  1670. " processorArchitecture=\"X86\"\n"++
  1671. " name=\"" ++ dropExtension exe_filename ++ "\"\n"++
  1672. " type=\"win32\"/>\n\n"++
  1673. " <trustInfo xmlns=\"urn:schemas-microsoft-com:asm.v3\">\n"++
  1674. " <security>\n"++
  1675. " <requestedPrivileges>\n"++
  1676. " <requestedExecutionLevel level=\"asInvoker\" uiAccess=\"false\"/>\n"++
  1677. " </requestedPrivileges>\n"++
  1678. " </security>\n"++
  1679. " </trustInfo>\n"++
  1680. "</assembly>\n"
  1681. -- Windows will find the manifest file if it is named
  1682. -- foo.exe.manifest. However, for extra robustness, and so that
  1683. -- we can move the binary around, we can embed the manifest in
  1684. -- the binary itself using windres:
  1685. if not (gopt Opt_EmbedManifest dflags) then return [] else do
  1686. rc_filename <- newTempName dflags "rc"
  1687. rc_obj_filename <- newTempName dflags (objectSuf dflags)
  1688. writeFile rc_filename $
  1689. "1 24 MOVEABLE PURE " ++ show manifest_filename ++ "\n"
  1690. -- magic numbers :-)
  1691. -- show is a bit hackish above, but we need to escape the
  1692. -- backslashes in the path.
  1693. let wr_opts = getOpts dflags opt_windres
  1694. runWindres dflags $ map SysTools.Option $
  1695. ["--input="++rc_filename,
  1696. "--output="++rc_obj_filename,
  1697. "--output-format=coff"]
  1698. ++ wr_opts
  1699. -- no FileOptions here: windres doesn't like seeing
  1700. -- backslashes, apparently
  1701. removeFile manifest_filename
  1702. return [rc_obj_filename]
  1703. | otherwise = return []
  1704. linkDynLibCheck :: DynFlags -> [String] -> [PackageId] -> IO ()
  1705. linkDynLibCheck dflags o_files dep_packages
  1706. = do
  1707. when (haveRtsOptsFlags dflags) $ do
  1708. log_action dflags dflags SevInfo noSrcSpan defaultUserStyle
  1709. (text "Warning: -rtsopts and -with-rtsopts have no effect with -shared." $$
  1710. text " Call hs_init_ghc() from your main() function to set these options.")
  1711. linkDynLib dflags o_files dep_packages
  1712. -- -----------------------------------------------------------------------------
  1713. -- Running CPP
  1714. doCpp :: DynFlags -> Bool -> Bool -> FilePath -> FilePath -> IO ()
  1715. doCpp dflags raw include_cc_opts input_fn output_fn = do
  1716. let hscpp_opts = getOpts dflags opt_P ++ picPOpts dflags
  1717. let cmdline_include_paths = includePaths dflags
  1718. pkg_include_dirs <- getPackageIncludePath dflags []
  1719. let include_paths = foldr (\ x xs -> "-I" : x : xs) []
  1720. (cmdline_include_paths ++ pkg_include_dirs)
  1721. let verbFlags = getVerbFlags dflags
  1722. let cc_opts
  1723. | include_cc_opts = getOpts dflags opt_c
  1724. | otherwise = []
  1725. let cpp_prog args | raw = SysTools.runCpp dflags args
  1726. | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
  1727. let target_defs =
  1728. [ "-D" ++ HOST_OS ++ "_BUILD_OS=1",
  1729. "-D" ++ HOST_ARCH ++ "_BUILD_ARCH=1",
  1730. "-D" ++ TARGET_OS ++ "_HOST_OS=1",
  1731. "-D" ++ TARGET_ARCH ++ "_HOST_ARCH=1" ]
  1732. -- remember, in code we *compile*, the HOST is the same our TARGET,
  1733. -- and BUILD is the same as our HOST.
  1734. let sse2 = isSse2Enabled dflags
  1735. sse4_2 = isSse4_2Enabled dflags
  1736. sse_defs =
  1737. [ "-D__SSE__=1" | sse2 || sse4_2 ] ++
  1738. [ "-D__SSE2__=1" | sse2 || sse4_2 ] ++
  1739. [ "-D__SSE4_2__=1" | sse4_2 ]
  1740. backend_defs <- getBackendDefs dflags
  1741. cpp_prog ( map SysTools.Option verbFlags
  1742. ++ map SysTools.Option include_paths
  1743. ++ map SysTools.Option hsSourceCppOpts
  1744. ++ map SysTools.Option target_defs
  1745. ++ map SysTools.Option backend_defs
  1746. ++ map SysTools.Option hscpp_opts
  1747. ++ map SysTools.Option cc_opts
  1748. ++ map SysTools.Option sse_defs
  1749. ++ [ SysTools.Option "-x"
  1750. , SysTools.Option "c"
  1751. , SysTools.Option input_fn
  1752. -- We hackily use Option instead of FileOption here, so that the file
  1753. -- name is not back-slashed on Windows. cpp is capable of
  1754. -- dealing with / in filenames, so it works fine. Furthermore
  1755. -- if we put in backslashes, cpp outputs #line directives
  1756. -- with *double* backslashes. And that in turn means that
  1757. -- our error messages get double backslashes in them.
  1758. -- In due course we should arrange that the lexer deals
  1759. -- with these \\ escapes properly.
  1760. , SysTools.Option "-o"
  1761. , SysTools.FileOption "" output_fn
  1762. ])
  1763. getBackendDefs :: DynFlags -> IO [String]
  1764. getBackendDefs dflags | hscTarget dflags == HscLlvm = do
  1765. llvmVer <- figureLlvmVersion dflags
  1766. return [ "-D__GLASGOW_HASKELL_LLVM__="++show llvmVer ]
  1767. getBackendDefs _ =
  1768. return []
  1769. hsSourceCppOpts :: [String]
  1770. -- Default CPP defines in Haskell source
  1771. hsSourceCppOpts =
  1772. [ "-D__GLASGOW_HASKELL__="++cProjectVersionInt ]
  1773. -- ---------------------------------------------------------------------------
  1774. -- join object files into a single relocatable object file, using ld -r
  1775. joinObjectFiles :: DynFlags -> [FilePath] -> FilePath -> IO ()
  1776. joinObjectFiles dflags o_files output_fn = do
  1777. let mySettings = settings dflags
  1778. ldIsGnuLd = sLdIsGnuLd mySettings
  1779. ld_r args = SysTools.runLink dflags ([
  1780. SysTools.Option "-nostdlib",
  1781. SysTools.Option "-nodefaultlibs",
  1782. SysTools.Option "-Wl,-r"
  1783. ]
  1784. -- gcc on sparc sets -Wl,--relax implicitly, but
  1785. -- -r and --relax are incompatible for ld, so
  1786. -- disable --relax explicitly.
  1787. ++ (if platformArch (targetPlatform dflags) == ArchSPARC
  1788. && ldIsGnuLd
  1789. then [SysTools.Option "-Wl,-no-relax"]
  1790. else [])
  1791. ++ map SysTools.Option ld_build_id
  1792. ++ [ SysTools.Option "-o",
  1793. SysTools.FileOption "" output_fn ]
  1794. ++ args)
  1795. -- suppress the generation of the .note.gnu.build-id section,
  1796. -- which we don't need and sometimes causes ld to emit a
  1797. -- warning:
  1798. ld_build_id | sLdSupportsBuildId mySettings = ["-Wl,--build-id=none"]
  1799. | otherwise = []
  1800. if ldIsGnuLd
  1801. then do
  1802. script <- newTempName dflags "ldscript"
  1803. writeFile script $ "INPUT(" ++ unwords o_files ++ ")"
  1804. ld_r [SysTools.FileOption "" script]
  1805. else if sLdSupportsFilelist mySettings
  1806. then do
  1807. filelist <- newTempName dflags "filelist"
  1808. writeFile filelist $ unlines o_files
  1809. ld_r [SysTools.Option "-Wl,-filelist",
  1810. SysTools.FileOption "-Wl," filelist]
  1811. else do
  1812. ld_r (map (SysTools.FileOption "") o_files)
  1813. -- -----------------------------------------------------------------------------
  1814. -- Misc.
  1815. -- | What phase to run after one of the backend code generators has run
  1816. hscPostBackendPhase :: DynFlags -> HscSource -> HscTarget -> Phase
  1817. hscPostBackendPhase _ HsBootFile _ = StopLn
  1818. hscPostBackendPhase dflags _ hsc_lang =
  1819. case hsc_lang of
  1820. HscC -> HCc
  1821. HscAsm | gopt Opt_SplitObjs dflags -> Splitter
  1822. | otherwise -> As
  1823. HscLlvm -> LlvmOpt
  1824. HscNothing -> StopLn
  1825. HscInterpreted -> StopLn
  1826. touchObjectFile :: DynFlags -> FilePath -> IO ()
  1827. touchObjectFile dflags path = do
  1828. createDirectoryIfMissing True $ takeDirectory path
  1829. SysTools.touch dflags "Touching object file" path
  1830. haveRtsOptsFlags :: DynFlags -> Bool
  1831. haveRtsOptsFlags dflags =
  1832. isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
  1833. RtsOptsSafeOnly -> False
  1834. _ -> True