Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
7c221f74
by Sylvain Henry at 2025-11-19T13:46:51-05:00
-
50dfc3a0
by Rodrigo Mesquita at 2025-11-19T13:46:52-05:00
28 changed files:
- compiler/GHC.hs
- + compiler/GHC/Driver/Config/Interpreter.hs
- compiler/GHC/Driver/Config/Linker.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Linker/Config.hs
- compiler/GHC/Linker/Dynamic.hs
- + compiler/GHC/Linker/Executable.hs
- − compiler/GHC/Linker/ExtraObj.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/MacOS.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/Linker/Windows.hs
- + compiler/GHC/Runtime/Interpreter/C.hs
- + compiler/GHC/Runtime/Interpreter/Init.hs
- compiler/GHC/SysTools/Tasks.hs
- compiler/ghc.cabal.in
- + testsuite/tests/bytecode/T23973.hs
- + testsuite/tests/bytecode/T23973.script
- + testsuite/tests/bytecode/T23973.stdout
- + testsuite/tests/bytecode/T26565.hs
- + testsuite/tests/bytecode/T26565.script
- + testsuite/tests/bytecode/T26565.stdout
- testsuite/tests/bytecode/all.T
- + testsuite/tests/driver/T24731.hs
- testsuite/tests/driver/all.T
- utils/iserv/iserv.cabal.in
Changes:
| ... | ... | @@ -337,7 +337,6 @@ module GHC ( |
| 337 | 337 | import GHC.Prelude hiding (init)
|
| 338 | 338 | |
| 339 | 339 | import GHC.Platform
|
| 340 | -import GHC.Platform.Ways
|
|
| 341 | 340 | |
| 342 | 341 | import GHC.Driver.Phases ( Phase(..), isHaskellSrcFilename
|
| 343 | 342 | , isSourceFilename, startPhase )
|
| ... | ... | @@ -351,7 +350,6 @@ import GHC.Driver.Backend |
| 351 | 350 | import GHC.Driver.Config.Finder (initFinderOpts)
|
| 352 | 351 | import GHC.Driver.Config.Parser (initParserOpts)
|
| 353 | 352 | import GHC.Driver.Config.Logger (initLogFlags)
|
| 354 | -import GHC.Driver.Config.StgToJS (initStgToJSConfig)
|
|
| 355 | 353 | import GHC.Driver.Config.Diagnostic
|
| 356 | 354 | import GHC.Driver.Main
|
| 357 | 355 | import GHC.Driver.Make
|
| ... | ... | @@ -360,10 +358,11 @@ import GHC.Driver.Monad |
| 360 | 358 | import GHC.Driver.Ppr
|
| 361 | 359 | |
| 362 | 360 | import GHC.ByteCode.Types
|
| 363 | -import qualified GHC.Linker.Loader as Loader
|
|
| 364 | 361 | import GHC.Runtime.Loader
|
| 365 | 362 | import GHC.Runtime.Eval
|
| 366 | 363 | import GHC.Runtime.Interpreter
|
| 364 | +import GHC.Runtime.Interpreter.Init
|
|
| 365 | +import GHC.Driver.Config.Interpreter
|
|
| 367 | 366 | import GHC.Runtime.Context
|
| 368 | 367 | import GHCi.RemoteTypes
|
| 369 | 368 | |
| ... | ... | @@ -439,10 +438,8 @@ import GHC.Unit.Module.ModSummary |
| 439 | 438 | import GHC.Unit.Module.Graph
|
| 440 | 439 | import GHC.Unit.Home.ModInfo
|
| 441 | 440 | import qualified GHC.Unit.Home.Graph as HUG
|
| 442 | -import GHC.Settings
|
|
| 443 | 441 | |
| 444 | 442 | import Control.Applicative ((<|>))
|
| 445 | -import Control.Concurrent
|
|
| 446 | 443 | import Control.Monad
|
| 447 | 444 | import Control.Monad.Catch as MC
|
| 448 | 445 | import Data.Foldable
|
| ... | ... | @@ -715,98 +712,16 @@ setTopSessionDynFlags :: GhcMonad m => DynFlags -> m () |
| 715 | 712 | setTopSessionDynFlags dflags = do
|
| 716 | 713 | hsc_env <- getSession
|
| 717 | 714 | logger <- getLogger
|
| 718 | - lookup_cache <- liftIO $ mkInterpSymbolCache
|
|
| 719 | - |
|
| 720 | - -- see Note [Target code interpreter]
|
|
| 721 | - interp <- if
|
|
| 722 | -#if !defined(wasm32_HOST_ARCH)
|
|
| 723 | - -- Wasm dynamic linker
|
|
| 724 | - | ArchWasm32 <- platformArch $ targetPlatform dflags
|
|
| 725 | - -> do
|
|
| 726 | - s <- liftIO $ newMVar InterpPending
|
|
| 727 | - loader <- liftIO Loader.uninitializedLoader
|
|
| 728 | - dyld <- liftIO $ makeAbsolute $ topDir dflags </> "dyld.mjs"
|
|
| 729 | - libdir <- liftIO $ last <$> Loader.getGccSearchDirectory logger dflags "libraries"
|
|
| 730 | - let profiled = ways dflags `hasWay` WayProf
|
|
| 731 | - way_tag = if profiled then "_p" else ""
|
|
| 732 | - let cfg =
|
|
| 733 | - WasmInterpConfig
|
|
| 734 | - { wasmInterpDyLD = dyld,
|
|
| 735 | - wasmInterpLibDir = libdir,
|
|
| 736 | - wasmInterpOpts = getOpts dflags opt_i,
|
|
| 737 | - wasmInterpBrowser = gopt Opt_GhciBrowser dflags,
|
|
| 738 | - wasmInterpBrowserHost = ghciBrowserHost dflags,
|
|
| 739 | - wasmInterpBrowserPort = ghciBrowserPort dflags,
|
|
| 740 | - wasmInterpBrowserRedirectWasiConsole = gopt Opt_GhciBrowserRedirectWasiConsole dflags,
|
|
| 741 | - wasmInterpBrowserPuppeteerLaunchOpts = ghciBrowserPuppeteerLaunchOpts dflags,
|
|
| 742 | - wasmInterpBrowserPlaywrightBrowserType = ghciBrowserPlaywrightBrowserType dflags,
|
|
| 743 | - wasmInterpBrowserPlaywrightLaunchOpts = ghciBrowserPlaywrightLaunchOpts dflags,
|
|
| 744 | - wasmInterpTargetPlatform = targetPlatform dflags,
|
|
| 745 | - wasmInterpProfiled = profiled,
|
|
| 746 | - wasmInterpHsSoSuffix = way_tag ++ dynLibSuffix (ghcNameVersion dflags),
|
|
| 747 | - wasmInterpUnitState = ue_homeUnitState $ hsc_unit_env hsc_env
|
|
| 748 | - }
|
|
| 749 | - pure $ Just $ Interp (ExternalInterp $ ExtWasm $ ExtInterpState cfg s) loader lookup_cache
|
|
| 750 | -#endif
|
|
| 751 | - |
|
| 752 | - -- JavaScript interpreter
|
|
| 753 | - | ArchJavaScript <- platformArch (targetPlatform dflags)
|
|
| 754 | - -> do
|
|
| 755 | - s <- liftIO $ newMVar InterpPending
|
|
| 756 | - loader <- liftIO Loader.uninitializedLoader
|
|
| 757 | - let cfg = JSInterpConfig
|
|
| 758 | - { jsInterpNodeConfig = defaultNodeJsSettings
|
|
| 759 | - , jsInterpScript = topDir dflags </> "ghc-interp.js"
|
|
| 760 | - , jsInterpTmpFs = hsc_tmpfs hsc_env
|
|
| 761 | - , jsInterpTmpDir = tmpDir dflags
|
|
| 762 | - , jsInterpLogger = hsc_logger hsc_env
|
|
| 763 | - , jsInterpCodegenCfg = initStgToJSConfig dflags
|
|
| 764 | - , jsInterpUnitEnv = hsc_unit_env hsc_env
|
|
| 765 | - , jsInterpFinderOpts = initFinderOpts dflags
|
|
| 766 | - , jsInterpFinderCache = hsc_FC hsc_env
|
|
| 767 | - }
|
|
| 768 | - return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader lookup_cache))
|
|
| 769 | - |
|
| 770 | - -- external interpreter
|
|
| 771 | - | gopt Opt_ExternalInterpreter dflags
|
|
| 772 | - -> do
|
|
| 773 | - let
|
|
| 774 | - prog = pgm_i dflags ++ flavour
|
|
| 775 | - profiled = ways dflags `hasWay` WayProf
|
|
| 776 | - dynamic = ways dflags `hasWay` WayDyn
|
|
| 777 | - flavour
|
|
| 778 | - | profiled && dynamic = "-prof-dyn"
|
|
| 779 | - | profiled = "-prof"
|
|
| 780 | - | dynamic = "-dyn"
|
|
| 781 | - | otherwise = ""
|
|
| 782 | - msg = text "Starting " <> text prog
|
|
| 783 | - tr <- if verbosity dflags >= 3
|
|
| 784 | - then return (logInfo logger $ withPprStyle defaultDumpStyle msg)
|
|
| 785 | - else return (pure ())
|
|
| 786 | - let
|
|
| 787 | - conf = IServConfig
|
|
| 788 | - { iservConfProgram = prog
|
|
| 789 | - , iservConfOpts = getOpts dflags opt_i
|
|
| 790 | - , iservConfProfiled = profiled
|
|
| 791 | - , iservConfDynamic = dynamic
|
|
| 792 | - , iservConfHook = createIservProcessHook (hsc_hooks hsc_env)
|
|
| 793 | - , iservConfTrace = tr
|
|
| 794 | - }
|
|
| 795 | - s <- liftIO $ newMVar InterpPending
|
|
| 796 | - loader <- liftIO Loader.uninitializedLoader
|
|
| 797 | - return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader lookup_cache))
|
|
| 798 | - |
|
| 799 | - -- Internal interpreter
|
|
| 800 | - | otherwise
|
|
| 801 | - ->
|
|
| 802 | -#if defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 803 | - do
|
|
| 804 | - loader <- liftIO Loader.uninitializedLoader
|
|
| 805 | - return (Just (Interp InternalInterp loader lookup_cache))
|
|
| 806 | -#else
|
|
| 807 | - return Nothing
|
|
| 808 | -#endif
|
|
| 809 | - |
|
| 715 | + let platform = targetPlatform dflags
|
|
| 716 | + let unit_env = hsc_unit_env hsc_env
|
|
| 717 | + let tmpfs = hsc_tmpfs hsc_env
|
|
| 718 | + let finder_cache = hsc_FC hsc_env
|
|
| 719 | + interp_opts' <- liftIO $ initInterpOpts dflags
|
|
| 720 | + let interp_opts = interp_opts'
|
|
| 721 | + { interpCreateProcess = createIservProcessHook (hsc_hooks hsc_env)
|
|
| 722 | + }
|
|
| 723 | + |
|
| 724 | + interp <- liftIO $ initInterpreter tmpfs logger platform finder_cache unit_env interp_opts
|
|
| 810 | 725 | |
| 811 | 726 | modifySession $ \h -> hscSetFlags dflags
|
| 812 | 727 | h{ hsc_IC = (hsc_IC h){ ic_dflags = dflags }
|
| 1 | +module GHC.Driver.Config.Interpreter
|
|
| 2 | + ( initInterpOpts
|
|
| 3 | + )
|
|
| 4 | +where
|
|
| 5 | + |
|
| 6 | +import GHC.Prelude
|
|
| 7 | +import GHC.Runtime.Interpreter.Init
|
|
| 8 | +import GHC.Driver.DynFlags
|
|
| 9 | +import GHC.Driver.Session
|
|
| 10 | +import GHC.Driver.Config.Finder
|
|
| 11 | +import GHC.Driver.Config.StgToJS
|
|
| 12 | +import GHC.SysTools.Tasks
|
|
| 13 | +import GHC.Linker.Executable
|
|
| 14 | + |
|
| 15 | +import System.FilePath
|
|
| 16 | +import System.Directory
|
|
| 17 | + |
|
| 18 | +initInterpOpts :: DynFlags -> IO InterpOpts
|
|
| 19 | +initInterpOpts dflags = do
|
|
| 20 | + wasm_dyld <- makeAbsolute $ topDir dflags </> "dyld.mjs"
|
|
| 21 | + js_interp <- makeAbsolute $ topDir dflags </> "ghc-interp.js"
|
|
| 22 | + pure $ InterpOpts
|
|
| 23 | + { interpExternal = gopt Opt_ExternalInterpreter dflags
|
|
| 24 | + , interpProg = pgm_i dflags
|
|
| 25 | + , interpOpts = getOpts dflags opt_i
|
|
| 26 | + , interpWays = ways dflags
|
|
| 27 | + , interpNameVer = ghcNameVersion dflags
|
|
| 28 | + , interpCreateProcess = Nothing
|
|
| 29 | + , interpWasmDyld = wasm_dyld
|
|
| 30 | + , interpBrowser = gopt Opt_GhciBrowser dflags
|
|
| 31 | + , interpBrowserHost = ghciBrowserHost dflags
|
|
| 32 | + , interpBrowserPort = ghciBrowserPort dflags
|
|
| 33 | + , interpBrowserRedirectWasiConsole = gopt Opt_GhciBrowserRedirectWasiConsole dflags
|
|
| 34 | + , interpBrowserPuppeteerLaunchOpts = ghciBrowserPuppeteerLaunchOpts dflags
|
|
| 35 | + , interpBrowserPlaywrightBrowserType = ghciBrowserPlaywrightBrowserType dflags
|
|
| 36 | + , interpBrowserPlaywrightLaunchOpts = ghciBrowserPlaywrightLaunchOpts dflags
|
|
| 37 | + , interpJsInterp = js_interp
|
|
| 38 | + , interpTmpDir = tmpDir dflags
|
|
| 39 | + , interpJsCodegenCfg = initStgToJSConfig dflags
|
|
| 40 | + , interpFinderOpts = initFinderOpts dflags
|
|
| 41 | + , interpVerbosity = verbosity dflags
|
|
| 42 | + , interpLdConfig = configureLd dflags
|
|
| 43 | + , interpCcConfig = configureCc dflags
|
|
| 44 | + , interpExecutableLinkOpts = initExecutableLinkOpts dflags
|
|
| 45 | + }
|
|
| 46 | + |
| ... | ... | @@ -10,6 +10,7 @@ import GHC.Linker.Config |
| 10 | 10 | |
| 11 | 11 | import GHC.Driver.DynFlags
|
| 12 | 12 | import GHC.Driver.Session
|
| 13 | +import GHC.Settings
|
|
| 13 | 14 | |
| 14 | 15 | import Data.List (isPrefixOf)
|
| 15 | 16 | |
| ... | ... | @@ -52,6 +53,8 @@ initLinkerConfig dflags = |
| 52 | 53 | , linkerOptionsPost = post_args
|
| 53 | 54 | , linkerTempDir = tmpDir dflags
|
| 54 | 55 | , linkerFilter = ld_filter
|
| 56 | + , linkerSupportsCompactUnwind = toolSettings_ldSupportsCompactUnwind (toolSettings dflags)
|
|
| 57 | + , linkerIsGnuLd = toolSettings_ldIsGnuLd (toolSettings dflags)
|
|
| 55 | 58 | }
|
| 56 | 59 | |
| 57 | 60 | {- Note [Solaris linker]
|
| ... | ... | @@ -28,7 +28,7 @@ module GHC.Driver.DynFlags ( |
| 28 | 28 | ParMakeCount(..),
|
| 29 | 29 | ways,
|
| 30 | 30 | HasDynFlags(..), ContainsDynFlags(..),
|
| 31 | - RtsOptsEnabled(..),
|
|
| 31 | + RtsOptsEnabled(..), haveRtsOptsFlags,
|
|
| 32 | 32 | GhcMode(..), isOneShot,
|
| 33 | 33 | GhcLink(..), isNoLink,
|
| 34 | 34 | PackageFlag(..), PackageArg(..), ModRenaming(..),
|
| ... | ... | @@ -902,6 +902,13 @@ data RtsOptsEnabled |
| 902 | 902 | | RtsOptsAll
|
| 903 | 903 | deriving (Show)
|
| 904 | 904 | |
| 905 | +haveRtsOptsFlags :: DynFlags -> Bool
|
|
| 906 | +haveRtsOptsFlags dflags =
|
|
| 907 | + isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
|
|
| 908 | + RtsOptsSafeOnly -> False
|
|
| 909 | + _ -> True
|
|
| 910 | + |
|
| 911 | + |
|
| 905 | 912 | -- | Are we building with @-fPIE@ or @-fPIC@ enabled?
|
| 906 | 913 | positionIndependent :: DynFlags -> Bool
|
| 907 | 914 | positionIndependent dflags = gopt Opt_PIC dflags || gopt Opt_PIE dflags
|
| ... | ... | @@ -71,7 +71,7 @@ import GHC.SysTools |
| 71 | 71 | import GHC.SysTools.Cpp
|
| 72 | 72 | import GHC.Utils.TmpFs
|
| 73 | 73 | |
| 74 | -import GHC.Linker.ExtraObj
|
|
| 74 | +import GHC.Linker.Executable
|
|
| 75 | 75 | import GHC.Linker.Static
|
| 76 | 76 | import GHC.Linker.Static.Utils
|
| 77 | 77 | import GHC.Linker.Types
|
| ... | ... | @@ -444,7 +444,9 @@ link' logger tmpfs fc dflags unit_env batch_attempt_linking mHscMessager hpt |
| 444 | 444 | case ghcLink dflags of
|
| 445 | 445 | LinkBinary
|
| 446 | 446 | | backendUseJSLinker (backend dflags) -> linkJSBinary logger tmpfs fc dflags unit_env obj_files pkg_deps
|
| 447 | - | otherwise -> linkBinary logger tmpfs dflags unit_env obj_files pkg_deps
|
|
| 447 | + | otherwise -> do
|
|
| 448 | + let opts = initExecutableLinkOpts dflags
|
|
| 449 | + linkExecutable logger tmpfs opts unit_env obj_files pkg_deps
|
|
| 448 | 450 | LinkStaticLib -> linkStaticLib logger dflags unit_env obj_files pkg_deps
|
| 449 | 451 | LinkDynLib -> linkDynLibCheck logger tmpfs dflags unit_env obj_files pkg_deps
|
| 450 | 452 | other -> panicBadLink other
|
| ... | ... | @@ -511,7 +513,8 @@ linkingNeeded logger dflags unit_env staticLink linkables pkg_deps = do |
| 511 | 513 | if not (null lib_errs) || any (t <) lib_times
|
| 512 | 514 | then return $ needsRecompileBecause LibraryChanged
|
| 513 | 515 | else do
|
| 514 | - res <- checkLinkInfo logger dflags unit_env pkg_deps exe_file
|
|
| 516 | + let opts = initExecutableLinkOpts dflags
|
|
| 517 | + res <- checkLinkInfo logger opts unit_env pkg_deps exe_file
|
|
| 515 | 518 | if res
|
| 516 | 519 | then return $ needsRecompileBecause FlagsChanged
|
| 517 | 520 | else return UpToDate
|
| ... | ... | @@ -585,7 +588,9 @@ doLink hsc_env o_files = do |
| 585 | 588 | LinkBinary
|
| 586 | 589 | | backendUseJSLinker (backend dflags)
|
| 587 | 590 | -> linkJSBinary logger tmpfs fc dflags unit_env o_files []
|
| 588 | - | otherwise -> linkBinary logger tmpfs dflags unit_env o_files []
|
|
| 591 | + | otherwise -> do
|
|
| 592 | + let opts = initExecutableLinkOpts dflags
|
|
| 593 | + linkExecutable logger tmpfs opts unit_env o_files []
|
|
| 589 | 594 | LinkStaticLib -> linkStaticLib logger dflags unit_env o_files []
|
| 590 | 595 | LinkDynLib -> linkDynLibCheck logger tmpfs dflags unit_env o_files []
|
| 591 | 596 | LinkMergedObj
|
| ... | ... | @@ -15,6 +15,7 @@ import Control.Monad |
| 15 | 15 | import Control.Monad.IO.Class
|
| 16 | 16 | import Control.Monad.Catch
|
| 17 | 17 | import GHC.Driver.Hooks
|
| 18 | +import GHC.Driver.DynFlags
|
|
| 18 | 19 | import Control.Monad.Trans.Reader
|
| 19 | 20 | import GHC.Driver.Pipeline.Monad
|
| 20 | 21 | import GHC.Driver.Pipeline.Phases
|
| ... | ... | @@ -74,7 +75,6 @@ import GHC.CmmToLlvm.Version.Type (LlvmVersion (..)) |
| 74 | 75 | import {-# SOURCE #-} GHC.Driver.Pipeline (compileForeign, compileEmptyStub)
|
| 75 | 76 | import GHC.Settings
|
| 76 | 77 | import System.IO
|
| 77 | -import GHC.Linker.ExtraObj
|
|
| 78 | 78 | import GHC.Linker.Dynamic
|
| 79 | 79 | import GHC.Utils.Panic
|
| 80 | 80 | import GHC.Utils.Touch
|
| ... | ... | @@ -416,6 +416,7 @@ runCcPhase cc_phase pipe_env hsc_env location input_fn = do |
| 416 | 416 | let unit_env = hsc_unit_env hsc_env
|
| 417 | 417 | let home_unit = hsc_home_unit_maybe hsc_env
|
| 418 | 418 | let tmpfs = hsc_tmpfs hsc_env
|
| 419 | + let tmpdir = tmpDir dflags
|
|
| 419 | 420 | let platform = ue_platform unit_env
|
| 420 | 421 | let hcc = cc_phase `eqPhase` HCc
|
| 421 | 422 | |
| ... | ... | @@ -437,7 +438,7 @@ runCcPhase cc_phase pipe_env hsc_env location input_fn = do |
| 437 | 438 | let include_paths = include_paths_quote ++ include_paths_global
|
| 438 | 439 | |
| 439 | 440 | let gcc_extra_viac_flags = extraGccViaCFlags dflags
|
| 440 | - let pic_c_flags = picCCOpts dflags
|
|
| 441 | + let cc_config = configureCc dflags
|
|
| 441 | 442 | |
| 442 | 443 | let verbFlags = getVerbFlags dflags
|
| 443 | 444 | |
| ... | ... | @@ -486,14 +487,14 @@ runCcPhase cc_phase pipe_env hsc_env location input_fn = do |
| 486 | 487 | ghcVersionH <- getGhcVersionIncludeFlags dflags unit_env
|
| 487 | 488 | |
| 488 | 489 | withAtomicRename output_fn $ \temp_outputFilename ->
|
| 489 | - GHC.SysTools.runCc (phaseForeignLanguage cc_phase) logger tmpfs dflags (
|
|
| 490 | + GHC.SysTools.runCc (phaseForeignLanguage cc_phase) logger tmpfs tmpdir cc_config (
|
|
| 490 | 491 | [ GHC.SysTools.Option "-c"
|
| 491 | 492 | , GHC.SysTools.FileOption "" input_fn
|
| 492 | 493 | , GHC.SysTools.Option "-o"
|
| 493 | 494 | , GHC.SysTools.FileOption "" temp_outputFilename
|
| 494 | 495 | ]
|
| 495 | 496 | ++ map GHC.SysTools.Option (
|
| 496 | - pic_c_flags
|
|
| 497 | + (ccPicOpts cc_config)
|
|
| 497 | 498 | |
| 498 | 499 | -- See Note [Produce big objects on Windows]
|
| 499 | 500 | ++ [ "-Wa,-mbig-obj"
|
| ... | ... | @@ -1149,7 +1150,8 @@ joinObjectFiles hsc_env o_files output_fn |
| 1149 | 1150 | |
| 1150 | 1151 | | otherwise = do
|
| 1151 | 1152 | withAtomicRename output_fn $ \tmp_ar ->
|
| 1152 | - liftIO $ runAr logger dflags Nothing $ map Option $ ["qc" ++ dashL, tmp_ar] ++ o_files
|
|
| 1153 | + let ar_opts = configureAr dflags
|
|
| 1154 | + in liftIO $ runAr logger ar_opts Nothing $ map Option $ ["qc" ++ dashL, tmp_ar] ++ o_files
|
|
| 1153 | 1155 | where
|
| 1154 | 1156 | dashLSupported = sArSupportsDashL (settings dflags)
|
| 1155 | 1157 | dashL = if dashLSupported then "L" else ""
|
| ... | ... | @@ -23,5 +23,7 @@ data LinkerConfig = LinkerConfig |
| 23 | 23 | , linkerOptionsPost :: [Option] -- ^ Linker options (after user options)
|
| 24 | 24 | , linkerTempDir :: TempDir -- ^ Temporary directory to use
|
| 25 | 25 | , linkerFilter :: [String] -> [String] -- ^ Output filter
|
| 26 | + , linkerSupportsCompactUnwind :: !Bool -- ^ Does the linker support compact unwind
|
|
| 27 | + , linkerIsGnuLd :: !Bool -- ^ Is it GNU LD (used for gc-sections support)
|
|
| 26 | 28 | }
|
| 27 | 29 |
| ... | ... | @@ -12,6 +12,7 @@ import GHC.Prelude |
| 12 | 12 | import GHC.Platform
|
| 13 | 13 | import GHC.Platform.Ways
|
| 14 | 14 | import GHC.Settings (ToolSettings(toolSettings_ldSupportsSingleModule))
|
| 15 | +import GHC.SysTools.Tasks
|
|
| 15 | 16 | |
| 16 | 17 | import GHC.Driver.Config.Linker
|
| 17 | 18 | import GHC.Driver.Session
|
| ... | ... | @@ -207,8 +208,10 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages |
| 207 | 208 | ++ [ Option "-Wl,-dead_strip_dylibs", Option "-Wl,-headerpad,8000" ]
|
| 208 | 209 | )
|
| 209 | 210 | -- Make sure to honour -fno-use-rpaths if set on darwin as well; see #20004
|
| 210 | - when (gopt Opt_RPath dflags) $
|
|
| 211 | - runInjectRPaths logger (toolSettings dflags) pkg_lib_paths output_fn
|
|
| 211 | + when (gopt Opt_RPath dflags) $ do
|
|
| 212 | + let otool_opts = configureOtool dflags
|
|
| 213 | + let install_name_opts = configureInstallName dflags
|
|
| 214 | + runInjectRPaths logger otool_opts install_name_opts pkg_lib_paths output_fn
|
|
| 212 | 215 | _ -> do
|
| 213 | 216 | -------------------------------------------------------------------
|
| 214 | 217 | -- Making a DSO
|
| 1 | +-- | Linking executables
|
|
| 2 | +module GHC.Linker.Executable
|
|
| 3 | + ( linkExecutable
|
|
| 4 | + , ExecutableLinkOpts (..)
|
|
| 5 | + , initExecutableLinkOpts
|
|
| 6 | + -- RTS Opts
|
|
| 7 | + , RtsOptsEnabled (..)
|
|
| 8 | + -- * Link info
|
|
| 9 | + , LinkInfo (..)
|
|
| 10 | + , initLinkInfo
|
|
| 11 | + , checkLinkInfo
|
|
| 12 | + , ghcLinkInfoSectionName
|
|
| 13 | + , ghcLinkInfoNoteName
|
|
| 14 | + , platformSupportsSavingLinkOpts
|
|
| 15 | + )
|
|
| 16 | +where
|
|
| 17 | + |
|
| 18 | +import GHC.Prelude
|
|
| 19 | +import GHC.Platform
|
|
| 20 | +import GHC.Platform.Ways
|
|
| 21 | + |
|
| 22 | +import GHC.Unit
|
|
| 23 | +import GHC.Unit.Env
|
|
| 24 | + |
|
| 25 | +import GHC.Utils.Asm
|
|
| 26 | +import GHC.Utils.Error
|
|
| 27 | +import GHC.Utils.Misc
|
|
| 28 | +import GHC.Utils.Outputable as Outputable
|
|
| 29 | +import GHC.Utils.Logger
|
|
| 30 | +import GHC.Utils.TmpFs
|
|
| 31 | + |
|
| 32 | +import GHC.Driver.Session
|
|
| 33 | +import GHC.Driver.Config.Linker
|
|
| 34 | + |
|
| 35 | +import qualified GHC.Data.ShortText as ST
|
|
| 36 | + |
|
| 37 | +import GHC.SysTools
|
|
| 38 | +import GHC.SysTools.Elf
|
|
| 39 | +import GHC.Linker.Config
|
|
| 40 | +import GHC.Linker.Unit
|
|
| 41 | +import GHC.Linker.MacOS
|
|
| 42 | +import GHC.Linker.Windows
|
|
| 43 | +import GHC.Linker.Dynamic (libmLinkOpts)
|
|
| 44 | +import GHC.Linker.External (runLink)
|
|
| 45 | +import GHC.Linker.Static.Utils (exeFileName)
|
|
| 46 | + |
|
| 47 | +import Control.Monad
|
|
| 48 | +import Data.Maybe
|
|
| 49 | +import System.FilePath
|
|
| 50 | +import System.Directory
|
|
| 51 | + |
|
| 52 | +data ExecutableLinkOpts = ExecutableLinkOpts
|
|
| 53 | + { leOutputFile :: Maybe FilePath
|
|
| 54 | + , leNameVersion :: GhcNameVersion
|
|
| 55 | + , leWays :: Ways
|
|
| 56 | + , leDynLibLoader :: DynLibLoader
|
|
| 57 | + , leRelativeDynlibPaths :: !Bool
|
|
| 58 | + , leUseXLinkerRPath :: !Bool
|
|
| 59 | + , leSingleLibFolder :: !Bool
|
|
| 60 | + , leWholeArchiveHsLibs :: !Bool
|
|
| 61 | + , leGenManifest :: !Bool
|
|
| 62 | + , leRPath :: !Bool
|
|
| 63 | + , leCompactUnwind :: !Bool
|
|
| 64 | + , leLibraryPaths :: [String]
|
|
| 65 | + , leFrameworkOpts :: FrameworkOpts
|
|
| 66 | + , leManifestOpts :: ManifestOpts
|
|
| 67 | + , leLinkerConfig :: LinkerConfig
|
|
| 68 | + , leOtoolConfig :: OtoolConfig
|
|
| 69 | + , leCcConfig :: CcConfig
|
|
| 70 | + , leInstallNameConfig :: InstallNameConfig
|
|
| 71 | + , leInputs :: [Option]
|
|
| 72 | + , lePieOpts :: [String]
|
|
| 73 | + , leTempDir :: TempDir
|
|
| 74 | + , leVerbFlags :: [String]
|
|
| 75 | + , leNoHsMain :: !Bool
|
|
| 76 | + , leMainSymbol :: String
|
|
| 77 | + , leRtsOptsEnabled :: !RtsOptsEnabled
|
|
| 78 | + , leRtsOptsSuggestions :: !Bool
|
|
| 79 | + , leKeepCafs :: !Bool
|
|
| 80 | + , leRtsOpts :: Maybe String
|
|
| 81 | + }
|
|
| 82 | + |
|
| 83 | +initExecutableLinkOpts :: DynFlags -> ExecutableLinkOpts
|
|
| 84 | +initExecutableLinkOpts dflags =
|
|
| 85 | + let
|
|
| 86 | + platform = targetPlatform dflags
|
|
| 87 | + os = platformOS platform
|
|
| 88 | + in ExecutableLinkOpts
|
|
| 89 | + { leOutputFile = outputFile_ dflags
|
|
| 90 | + , leNameVersion = ghcNameVersion dflags
|
|
| 91 | + , leWays = ways dflags
|
|
| 92 | + , leDynLibLoader = dynLibLoader dflags
|
|
| 93 | + , leRelativeDynlibPaths = gopt Opt_RelativeDynlibPaths dflags
|
|
| 94 | + , leUseXLinkerRPath = useXLinkerRPath dflags os
|
|
| 95 | + , leSingleLibFolder = gopt Opt_SingleLibFolder dflags
|
|
| 96 | + , leWholeArchiveHsLibs = gopt Opt_WholeArchiveHsLibs dflags
|
|
| 97 | + , leGenManifest = gopt Opt_GenManifest dflags
|
|
| 98 | + , leRPath = gopt Opt_RPath dflags
|
|
| 99 | + , leCompactUnwind = gopt Opt_CompactUnwind dflags
|
|
| 100 | + , leLibraryPaths = libraryPaths dflags
|
|
| 101 | + , leFrameworkOpts = initFrameworkOpts dflags
|
|
| 102 | + , leManifestOpts = initManifestOpts dflags
|
|
| 103 | + , leLinkerConfig = initLinkerConfig dflags
|
|
| 104 | + , leCcConfig = configureCc dflags
|
|
| 105 | + , leOtoolConfig = configureOtool dflags
|
|
| 106 | + , leInstallNameConfig = configureInstallName dflags
|
|
| 107 | + , leInputs = ldInputs dflags
|
|
| 108 | + , lePieOpts = pieCCLDOpts dflags
|
|
| 109 | + , leTempDir = tmpDir dflags
|
|
| 110 | + , leVerbFlags = getVerbFlags dflags
|
|
| 111 | + , leNoHsMain = gopt Opt_NoHsMain dflags
|
|
| 112 | + , leMainSymbol = "ZCMain_main"
|
|
| 113 | + , leRtsOptsEnabled = rtsOptsEnabled dflags
|
|
| 114 | + , leRtsOptsSuggestions = rtsOptsSuggestions dflags
|
|
| 115 | + , leKeepCafs = gopt Opt_KeepCAFs dflags
|
|
| 116 | + , leRtsOpts = rtsOpts dflags
|
|
| 117 | + }
|
|
| 118 | + |
|
| 119 | +leHaveRtsOptsFlags :: ExecutableLinkOpts -> Bool
|
|
| 120 | +leHaveRtsOptsFlags opts =
|
|
| 121 | + isJust (leRtsOpts opts)
|
|
| 122 | + || case leRtsOptsEnabled opts of
|
|
| 123 | + RtsOptsSafeOnly -> False
|
|
| 124 | + _ -> True
|
|
| 125 | + |
|
| 126 | +linkExecutable :: Logger -> TmpFs -> ExecutableLinkOpts -> UnitEnv -> [FilePath] -> [UnitId] -> IO ()
|
|
| 127 | +linkExecutable logger tmpfs opts unit_env o_files dep_units = do
|
|
| 128 | + let static_link = False
|
|
| 129 | + let platform = ue_platform unit_env
|
|
| 130 | + unit_state = ue_homeUnitState unit_env
|
|
| 131 | + verbFlags = leVerbFlags opts
|
|
| 132 | + arch_os = platformArchOS platform
|
|
| 133 | + output_fn = exeFileName arch_os static_link (leOutputFile opts)
|
|
| 134 | + namever = leNameVersion opts
|
|
| 135 | + -- For the wasm target, when ghc is invoked with -dynamic,
|
|
| 136 | + -- when linking the final .wasm binary we must still ensure
|
|
| 137 | + -- the static archives are selected. Otherwise wasm-ld would
|
|
| 138 | + -- fail to find and link the .so library dependencies. wasm-ld
|
|
| 139 | + -- can link PIC objects into static .wasm binaries fine, so we
|
|
| 140 | + -- only adjust the ways in the final linking step, and only
|
|
| 141 | + -- when linking .wasm binary (which is supposed to be fully
|
|
| 142 | + -- static), not when linking .so shared libraries.
|
|
| 143 | + ways_
|
|
| 144 | + | ArchWasm32 <- platformArch platform = removeWay WayDyn $ leWays opts
|
|
| 145 | + | otherwise = leWays opts
|
|
| 146 | + |
|
| 147 | + full_output_fn <- if isAbsolute output_fn
|
|
| 148 | + then return output_fn
|
|
| 149 | + else do d <- getCurrentDirectory
|
|
| 150 | + return $ normalise (d </> output_fn)
|
|
| 151 | + |
|
| 152 | + -- get the full list of packages to link with, by combining the
|
|
| 153 | + -- explicit packages with the auto packages and all of their
|
|
| 154 | + -- dependencies, and eliminating duplicates.
|
|
| 155 | + pkgs <- mayThrowUnitErr (preloadUnitsInfo' unit_env dep_units)
|
|
| 156 | + let pkg_lib_paths = collectLibraryDirs ways_ pkgs
|
|
| 157 | + let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
|
|
| 158 | + get_pkg_lib_path_opts l
|
|
| 159 | + | osElfTarget (platformOS platform) &&
|
|
| 160 | + leDynLibLoader opts == SystemDependent &&
|
|
| 161 | + ways_ `hasWay` WayDyn
|
|
| 162 | + = let libpath = if leRelativeDynlibPaths opts
|
|
| 163 | + then "$ORIGIN" </>
|
|
| 164 | + (l `makeRelativeTo` full_output_fn)
|
|
| 165 | + else l
|
|
| 166 | + -- See Note [-Xlinker -rpath vs -Wl,-rpath]
|
|
| 167 | + rpath = if leUseXLinkerRPath opts
|
|
| 168 | + then ["-Xlinker", "-rpath", "-Xlinker", libpath]
|
|
| 169 | + else []
|
|
| 170 | + -- Solaris 11's linker does not support -rpath-link option. It silently
|
|
| 171 | + -- ignores it and then complains about next option which is -l<some
|
|
| 172 | + -- dir> as being a directory and not expected object file, E.g
|
|
| 173 | + -- ld: elf error: file
|
|
| 174 | + -- /tmp/ghc-src/libraries/base/dist-install/build:
|
|
| 175 | + -- elf_begin: I/O error: region read: Is a directory
|
|
| 176 | + rpathlink = if (platformOS platform) == OSSolaris2
|
|
| 177 | + then []
|
|
| 178 | + else ["-Xlinker", "-rpath-link", "-Xlinker", l]
|
|
| 179 | + in ["-L" ++ l] ++ rpathlink ++ rpath
|
|
| 180 | + | osMachOTarget (platformOS platform) &&
|
|
| 181 | + leDynLibLoader opts == SystemDependent &&
|
|
| 182 | + ways_ `hasWay` WayDyn &&
|
|
| 183 | + leUseXLinkerRPath opts
|
|
| 184 | + = let libpath = if leRelativeDynlibPaths opts
|
|
| 185 | + then "@loader_path" </>
|
|
| 186 | + (l `makeRelativeTo` full_output_fn)
|
|
| 187 | + else l
|
|
| 188 | + in ["-L" ++ l] ++ ["-Xlinker", "-rpath", "-Xlinker", libpath]
|
|
| 189 | + | otherwise = ["-L" ++ l]
|
|
| 190 | + |
|
| 191 | + pkg_lib_path_opts <-
|
|
| 192 | + if leSingleLibFolder opts
|
|
| 193 | + then do
|
|
| 194 | + libs <- getLibs namever ways_ unit_env dep_units
|
|
| 195 | + tmpDir <- newTempSubDir logger tmpfs (leTempDir opts)
|
|
| 196 | + sequence_ [ copyFile lib (tmpDir </> basename)
|
|
| 197 | + | (lib, basename) <- libs]
|
|
| 198 | + return [ "-L" ++ tmpDir ]
|
|
| 199 | + else pure pkg_lib_path_opts
|
|
| 200 | + |
|
| 201 | + let
|
|
| 202 | + dead_strip
|
|
| 203 | + | leWholeArchiveHsLibs opts = []
|
|
| 204 | + | otherwise = if osSubsectionsViaSymbols (platformOS platform)
|
|
| 205 | + then ["-Wl,-dead_strip"]
|
|
| 206 | + else []
|
|
| 207 | + let lib_paths = leLibraryPaths opts
|
|
| 208 | + let lib_path_opts = map ("-L"++) lib_paths
|
|
| 209 | + |
|
| 210 | + extraLinkObj <- maybeToList <$> mkExtraObjToLinkIntoBinary logger tmpfs opts unit_state
|
|
| 211 | + noteLinkObjs <- mkNoteObjsToLinkIntoBinary logger tmpfs opts unit_env dep_units
|
|
| 212 | + |
|
| 213 | + let
|
|
| 214 | + (pre_hs_libs, post_hs_libs)
|
|
| 215 | + | leWholeArchiveHsLibs opts
|
|
| 216 | + = if platformOS platform == OSDarwin
|
|
| 217 | + then (["-Wl,-all_load"], [])
|
|
| 218 | + -- OS X does not have a flag to turn off -all_load
|
|
| 219 | + else (["-Wl,--whole-archive"], ["-Wl,--no-whole-archive"])
|
|
| 220 | + | otherwise
|
|
| 221 | + = ([],[])
|
|
| 222 | + |
|
| 223 | + pkg_link_opts <- do
|
|
| 224 | + unit_link_opts <- getUnitLinkOpts namever ways_ unit_env dep_units
|
|
| 225 | + return $ otherFlags unit_link_opts ++ dead_strip
|
|
| 226 | + ++ pre_hs_libs ++ hsLibs unit_link_opts ++ post_hs_libs
|
|
| 227 | + ++ extraLibs unit_link_opts
|
|
| 228 | + -- -Wl,-u,<sym> contained in other_flags
|
|
| 229 | + -- needs to be put before -l<package>,
|
|
| 230 | + -- otherwise Solaris linker fails linking
|
|
| 231 | + -- a binary with unresolved symbols in RTS
|
|
| 232 | + -- which are defined in base package
|
|
| 233 | + -- the reason for this is a note in ld(1) about
|
|
| 234 | + -- '-u' option: "The placement of this option
|
|
| 235 | + -- on the command line is significant.
|
|
| 236 | + -- This option must be placed before the library
|
|
| 237 | + -- that defines the symbol."
|
|
| 238 | + |
|
| 239 | + -- frameworks
|
|
| 240 | + pkg_framework_opts <- getUnitFrameworkOpts unit_env dep_units
|
|
| 241 | + let framework_opts = getFrameworkOpts (leFrameworkOpts opts) platform
|
|
| 242 | + |
|
| 243 | + -- probably _stub.o files
|
|
| 244 | + let extra_ld_inputs = leInputs opts
|
|
| 245 | + |
|
| 246 | + rc_objs <- case platformOS platform of
|
|
| 247 | + OSMinGW32 | leGenManifest opts -> maybeCreateManifest logger tmpfs (leManifestOpts opts) output_fn
|
|
| 248 | + _ -> return []
|
|
| 249 | + |
|
| 250 | + let linker_config = leLinkerConfig opts
|
|
| 251 | + let args = ( map GHC.SysTools.Option verbFlags
|
|
| 252 | + ++ [ GHC.SysTools.Option "-o"
|
|
| 253 | + , GHC.SysTools.FileOption "" output_fn
|
|
| 254 | + ]
|
|
| 255 | + ++ libmLinkOpts platform
|
|
| 256 | + ++ map GHC.SysTools.Option (
|
|
| 257 | + []
|
|
| 258 | + |
|
| 259 | + -- See Note [No PIE when linking]
|
|
| 260 | + ++ lePieOpts opts
|
|
| 261 | + |
|
| 262 | + -- Permit the linker to auto link _symbol to _imp_symbol.
|
|
| 263 | + -- This lets us link against DLLs without needing an "import library".
|
|
| 264 | + ++ (if platformOS platform == OSMinGW32
|
|
| 265 | + then ["-Wl,--enable-auto-import"]
|
|
| 266 | + else [])
|
|
| 267 | + |
|
| 268 | + -- '-no_compact_unwind'
|
|
| 269 | + -- C++/Objective-C exceptions cannot use optimised
|
|
| 270 | + -- stack unwinding code. The optimised form is the
|
|
| 271 | + -- default in Xcode 4 on at least x86_64, and
|
|
| 272 | + -- without this flag we're also seeing warnings
|
|
| 273 | + -- like
|
|
| 274 | + -- ld: warning: could not create compact unwind for .LFB3: non-standard register 5 being saved in prolog
|
|
| 275 | + -- on x86.
|
|
| 276 | + ++ (if not (leCompactUnwind opts) &&
|
|
| 277 | + linkerSupportsCompactUnwind (leLinkerConfig opts) &&
|
|
| 278 | + (platformOS platform == OSDarwin) &&
|
|
| 279 | + case platformArch platform of
|
|
| 280 | + ArchX86_64 -> True
|
|
| 281 | + ArchAArch64 -> True
|
|
| 282 | + _ -> False
|
|
| 283 | + then ["-Wl,-no_compact_unwind"]
|
|
| 284 | + else [])
|
|
| 285 | + |
|
| 286 | + -- We should rather be asking does it support --gc-sections?
|
|
| 287 | + ++ (if linkerIsGnuLd (leLinkerConfig opts) &&
|
|
| 288 | + not (leWholeArchiveHsLibs opts)
|
|
| 289 | + then ["-Wl,--gc-sections"]
|
|
| 290 | + else [])
|
|
| 291 | + |
|
| 292 | + ++ o_files
|
|
| 293 | + ++ lib_path_opts)
|
|
| 294 | + ++ extra_ld_inputs
|
|
| 295 | + ++ map GHC.SysTools.Option (
|
|
| 296 | + rc_objs
|
|
| 297 | + ++ framework_opts
|
|
| 298 | + ++ pkg_lib_path_opts
|
|
| 299 | + ++ extraLinkObj
|
|
| 300 | + ++ noteLinkObjs
|
|
| 301 | + -- See Note [RTS/ghc-internal interface]
|
|
| 302 | + -- (-u<sym> must come before -lghc-internal...!)
|
|
| 303 | + ++ (if ghcInternalUnitId `elem` map unitId pkgs
|
|
| 304 | + then [concat [ "-Wl,-u,"
|
|
| 305 | + , ['_' | platformLeadingUnderscore platform]
|
|
| 306 | + , "init_ghc_hs_iface" ]]
|
|
| 307 | + else [])
|
|
| 308 | + ++ pkg_link_opts
|
|
| 309 | + ++ pkg_framework_opts
|
|
| 310 | + ++ (if platformOS platform == OSDarwin
|
|
| 311 | + -- dead_strip_dylibs, will remove unused dylibs, and thus save
|
|
| 312 | + -- space in the load commands. The -headerpad is necessary so
|
|
| 313 | + -- that we can inject more @rpath's later for the left over
|
|
| 314 | + -- libraries during runInjectRpaths phase.
|
|
| 315 | + --
|
|
| 316 | + -- See Note [Dynamic linking on macOS].
|
|
| 317 | + then [ "-Wl,-dead_strip_dylibs", "-Wl,-headerpad,8000" ]
|
|
| 318 | + else [])
|
|
| 319 | + ))
|
|
| 320 | + |
|
| 321 | + runLink logger tmpfs linker_config args
|
|
| 322 | + |
|
| 323 | + -- Make sure to honour -fno-use-rpaths if set on darwin as well; see #20004
|
|
| 324 | + when (platformOS platform == OSDarwin && leRPath opts) $
|
|
| 325 | + GHC.Linker.MacOS.runInjectRPaths logger (leOtoolConfig opts) (leInstallNameConfig opts) pkg_lib_paths output_fn
|
|
| 326 | + |
|
| 327 | +mkExtraObj :: Logger -> TmpFs -> TempDir -> CcConfig -> UnitState -> Suffix -> String -> IO FilePath
|
|
| 328 | +mkExtraObj logger tmpfs tmpdir cc_config unit_state extn xs
|
|
| 329 | + = do
|
|
| 330 | + -- Pass a different set of options to the C compiler depending one whether
|
|
| 331 | + -- we're compiling C or assembler. When compiling C, we pass the usual
|
|
| 332 | + -- set of include directories and PIC flags.
|
|
| 333 | + let cOpts = map Option (ccPicOpts cc_config)
|
|
| 334 | + ++ map (FileOption "-I" . ST.unpack)
|
|
| 335 | + (unitIncludeDirs $ unsafeLookupUnit unit_state rtsUnit)
|
|
| 336 | + cFile <- newTempName logger tmpfs tmpdir TFL_CurrentModule extn
|
|
| 337 | + oFile <- newTempName logger tmpfs tmpdir TFL_GhcSession "o"
|
|
| 338 | + writeFile cFile xs
|
|
| 339 | + runCc Nothing logger tmpfs tmpdir cc_config
|
|
| 340 | + ([Option "-c",
|
|
| 341 | + FileOption "" cFile,
|
|
| 342 | + Option "-o",
|
|
| 343 | + FileOption "" oFile]
|
|
| 344 | + ++ if extn /= "s"
|
|
| 345 | + then cOpts
|
|
| 346 | + else [])
|
|
| 347 | + return oFile
|
|
| 348 | + |
|
| 349 | +-- | Create object containing main() entry point
|
|
| 350 | +--
|
|
| 351 | +-- When linking a binary, we need to create a C main() function that
|
|
| 352 | +-- starts everything off. This used to be compiled statically as part
|
|
| 353 | +-- of the RTS, but that made it hard to change the -rtsopts setting,
|
|
| 354 | +-- so now we generate and compile a main() stub as part of every
|
|
| 355 | +-- binary and pass the -rtsopts setting directly to the RTS (#5373)
|
|
| 356 | +mkExtraObjToLinkIntoBinary :: Logger -> TmpFs -> ExecutableLinkOpts -> UnitState -> IO (Maybe FilePath)
|
|
| 357 | +mkExtraObjToLinkIntoBinary logger tmpfs opts unit_state = do
|
|
| 358 | + when (leNoHsMain opts && leHaveRtsOptsFlags opts) $
|
|
| 359 | + logInfo logger $ withPprStyle defaultUserStyle
|
|
| 360 | + (text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
|
|
| 361 | + text " Call hs_init_ghc() from your main() function to set these options.")
|
|
| 362 | + |
|
| 363 | + if leNoHsMain opts
|
|
| 364 | + -- Don't try to build the extra object if it is not needed. Compiling the
|
|
| 365 | + -- extra object assumes the presence of the RTS in the unit database
|
|
| 366 | + -- (because the extra object imports Rts.h) but GHC's build system may try
|
|
| 367 | + -- to build some helper programs before building and registering the RTS!
|
|
| 368 | + -- See #18938 for an example where hp2ps failed to build because of a failed
|
|
| 369 | + -- (unsafe) lookup for the RTS in the unit db.
|
|
| 370 | + then pure Nothing
|
|
| 371 | + else mk_extra_obj exeMain
|
|
| 372 | + |
|
| 373 | + where
|
|
| 374 | + tmpdir = leTempDir opts
|
|
| 375 | + cc_config = leCcConfig opts
|
|
| 376 | + mk_extra_obj = fmap Just . mkExtraObj logger tmpfs tmpdir cc_config unit_state "c" . renderWithContext defaultSDocContext
|
|
| 377 | + |
|
| 378 | + exeMain = vcat [
|
|
| 379 | + text "#include <Rts.h>",
|
|
| 380 | + text "extern StgClosure " <> text (leMainSymbol opts) <> text "_closure;",
|
|
| 381 | + text "int main(int argc, char *argv[])",
|
|
| 382 | + char '{',
|
|
| 383 | + text " RtsConfig __conf = defaultRtsConfig;",
|
|
| 384 | + text " __conf.rts_opts_enabled = "
|
|
| 385 | + <> text (show (leRtsOptsEnabled opts)) <> semi,
|
|
| 386 | + text " __conf.rts_opts_suggestions = "
|
|
| 387 | + <> (if leRtsOptsSuggestions opts
|
|
| 388 | + then text "true"
|
|
| 389 | + else text "false") <> semi,
|
|
| 390 | + text "__conf.keep_cafs = "
|
|
| 391 | + <> (if leKeepCafs opts
|
|
| 392 | + then text "true"
|
|
| 393 | + else text "false") <> semi,
|
|
| 394 | + case leRtsOpts opts of
|
|
| 395 | + Nothing -> Outputable.empty
|
|
| 396 | + Just rts_opts -> text " __conf.rts_opts= " <>
|
|
| 397 | + text (show rts_opts) <> semi,
|
|
| 398 | + text " __conf.rts_hs_main = true;",
|
|
| 399 | + text " return hs_main(argc,argv,&" <> text (leMainSymbol opts) <> text "_closure,__conf);",
|
|
| 400 | + char '}',
|
|
| 401 | + char '\n' -- final newline, to keep gcc happy
|
|
| 402 | + ]
|
|
| 403 | + |
|
| 404 | +-- Write out the link info section into a new assembly file. Previously
|
|
| 405 | +-- this was included as inline assembly in the main.c file but this
|
|
| 406 | +-- is pretty fragile. gas gets upset trying to calculate relative offsets
|
|
| 407 | +-- that span the .note section (notably .text) when debug info is present
|
|
| 408 | +mkNoteObjsToLinkIntoBinary :: Logger -> TmpFs -> ExecutableLinkOpts -> UnitEnv -> [UnitId] -> IO [FilePath]
|
|
| 409 | +mkNoteObjsToLinkIntoBinary logger tmpfs opts unit_env dep_packages = do
|
|
| 410 | + link_info <- initLinkInfo opts unit_env dep_packages
|
|
| 411 | + |
|
| 412 | + if (platformSupportsSavingLinkOpts (platformOS platform ))
|
|
| 413 | + then fmap (:[]) $ mkExtraObj logger tmpfs tmpdir cc_config unit_state "s" (renderWithContext defaultSDocContext (link_opts link_info))
|
|
| 414 | + else return []
|
|
| 415 | + |
|
| 416 | + where
|
|
| 417 | + unit_state = ue_homeUnitState unit_env
|
|
| 418 | + platform = ue_platform unit_env
|
|
| 419 | + tmpdir = leTempDir opts
|
|
| 420 | + cc_config = leCcConfig opts
|
|
| 421 | + link_opts info = hcat
|
|
| 422 | + [ -- "link info" section (see Note [LinkInfo section])
|
|
| 423 | + makeElfNote platform ghcLinkInfoSectionName ghcLinkInfoNoteName 0 (show info)
|
|
| 424 | + |
|
| 425 | + -- ALL generated assembly must have this section to disable
|
|
| 426 | + -- executable stacks. See also
|
|
| 427 | + -- "GHC.CmmToAsm" for another instance
|
|
| 428 | + -- where we need to do this.
|
|
| 429 | + , if platformHasGnuNonexecStack platform
|
|
| 430 | + then text ".section .note.GNU-stack,\"\","
|
|
| 431 | + <> sectionType platform "progbits" <> char '\n'
|
|
| 432 | + else Outputable.empty
|
|
| 433 | + ]
|
|
| 434 | + |
|
| 435 | +data LinkInfo = LinkInfo
|
|
| 436 | + { liPkgLinkOpts :: UnitLinkOpts
|
|
| 437 | + , liPkgFrameworks :: [String]
|
|
| 438 | + , liRtsOpts :: Maybe String
|
|
| 439 | + , liRtsOptsEnabled :: !RtsOptsEnabled
|
|
| 440 | + , liNoHsMain :: !Bool
|
|
| 441 | + , liLdInputs :: [String]
|
|
| 442 | + , liLdOpts :: [String]
|
|
| 443 | + }
|
|
| 444 | + deriving (Show)
|
|
| 445 | + |
|
| 446 | + |
|
| 447 | +-- | Return the "link info"
|
|
| 448 | +--
|
|
| 449 | +-- See Note [LinkInfo section]
|
|
| 450 | +initLinkInfo :: ExecutableLinkOpts -> UnitEnv -> [UnitId] -> IO LinkInfo
|
|
| 451 | +initLinkInfo opts unit_env dep_packages = do
|
|
| 452 | + package_link_opts <- getUnitLinkOpts (leNameVersion opts) (leWays opts) unit_env dep_packages
|
|
| 453 | + pkg_frameworks <- if not (platformUsesFrameworks (ue_platform unit_env))
|
|
| 454 | + then return []
|
|
| 455 | + else do
|
|
| 456 | + ps <- mayThrowUnitErr (preloadUnitsInfo' unit_env dep_packages)
|
|
| 457 | + return (collectFrameworks ps)
|
|
| 458 | + pure $ LinkInfo
|
|
| 459 | + { liPkgLinkOpts = package_link_opts
|
|
| 460 | + , liPkgFrameworks = pkg_frameworks
|
|
| 461 | + , liRtsOpts = leRtsOpts opts
|
|
| 462 | + , liRtsOptsEnabled = leRtsOptsEnabled opts
|
|
| 463 | + , liNoHsMain = leNoHsMain opts
|
|
| 464 | + , liLdInputs = map showOpt (leInputs opts)
|
|
| 465 | + , liLdOpts = map showOpt (linkerOptionsPost (leLinkerConfig opts))
|
|
| 466 | + }
|
|
| 467 | + |
|
| 468 | +platformSupportsSavingLinkOpts :: OS -> Bool
|
|
| 469 | +platformSupportsSavingLinkOpts os
|
|
| 470 | + | os == OSSolaris2 = False -- see #5382
|
|
| 471 | + | otherwise = osElfTarget os
|
|
| 472 | + |
|
| 473 | +-- See Note [LinkInfo section]
|
|
| 474 | +ghcLinkInfoSectionName :: String
|
|
| 475 | +ghcLinkInfoSectionName = ".debug-ghc-link-info"
|
|
| 476 | + -- if we use the ".debug" prefix, then strip will strip it by default
|
|
| 477 | + |
|
| 478 | +-- Identifier for the note (see Note [LinkInfo section])
|
|
| 479 | +ghcLinkInfoNoteName :: String
|
|
| 480 | +ghcLinkInfoNoteName = "GHC link info"
|
|
| 481 | + |
|
| 482 | +-- Returns 'False' if it was, and we can avoid linking, because the
|
|
| 483 | +-- previous binary was linked with "the same options".
|
|
| 484 | +checkLinkInfo :: Logger -> ExecutableLinkOpts -> UnitEnv -> [UnitId] -> FilePath -> IO Bool
|
|
| 485 | +checkLinkInfo logger opts unit_env pkg_deps exe_file
|
|
| 486 | + | not (platformSupportsSavingLinkOpts (platformOS (ue_platform unit_env)))
|
|
| 487 | + -- ToDo: Windows and OS X do not use the ELF binary format, so
|
|
| 488 | + -- readelf does not work there. We need to find another way to do
|
|
| 489 | + -- this.
|
|
| 490 | + = return False -- conservatively we should return True, but not
|
|
| 491 | + -- linking in this case was the behaviour for a long
|
|
| 492 | + -- time so we leave it as-is.
|
|
| 493 | + | otherwise
|
|
| 494 | + = do
|
|
| 495 | + link_info <- initLinkInfo opts unit_env pkg_deps
|
|
| 496 | + debugTraceMsg logger 3 $ text ("Link info: " ++ show link_info)
|
|
| 497 | + m_exe_link_info <- readElfNoteAsString logger exe_file
|
|
| 498 | + ghcLinkInfoSectionName ghcLinkInfoNoteName
|
|
| 499 | + let sameLinkInfo = (Just (show link_info) == m_exe_link_info)
|
|
| 500 | + debugTraceMsg logger 3 $ case m_exe_link_info of
|
|
| 501 | + Nothing -> text "Exe link info: Not found"
|
|
| 502 | + Just s
|
|
| 503 | + | sameLinkInfo -> text ("Exe link info is the same")
|
|
| 504 | + | otherwise -> text ("Exe link info is different: " ++ s)
|
|
| 505 | + return (not sameLinkInfo)
|
|
| 506 | + |
|
| 507 | +{- Note [LinkInfo section]
|
|
| 508 | + ~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 509 | + |
|
| 510 | +The "link info" is a string representing the parameters of the link. We save
|
|
| 511 | +this information in the binary, and the next time we link, if nothing else has
|
|
| 512 | +changed, we use the link info stored in the existing binary to decide whether
|
|
| 513 | +to re-link or not.
|
|
| 514 | + |
|
| 515 | +The "link info" string is stored in a ELF section called ".debug-ghc-link-info"
|
|
| 516 | +(see ghcLinkInfoSectionName) with the SHT_NOTE type. For some time, it used to
|
|
| 517 | +not follow the specified record-based format (see #11022).
|
|
| 518 | + |
|
| 519 | +-}
|
|
| 520 | + |
|
| 521 | +{-
|
|
| 522 | +Note [-Xlinker -rpath vs -Wl,-rpath]
|
|
| 523 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 524 | + |
|
| 525 | +-Wl takes a comma-separated list of options which in the case of
|
|
| 526 | +-Wl,-rpath -Wl,some,path,with,commas parses the path with commas
|
|
| 527 | +as separate options.
|
|
| 528 | +Buck, the build system, produces paths with commas in them.
|
|
| 529 | + |
|
| 530 | +-Xlinker doesn't have this disadvantage and as far as I can tell
|
|
| 531 | +it is supported by both gcc and clang. Anecdotally nvcc supports
|
|
| 532 | +-Xlinker, but not -Wl.
|
|
| 533 | +-}
|
|
| 534 | + |
| 1 | ------------------------------------------------------------------------------
|
|
| 2 | ---
|
|
| 3 | --- GHC Extra object linking code
|
|
| 4 | ---
|
|
| 5 | --- (c) The GHC Team 2017
|
|
| 6 | ---
|
|
| 7 | ------------------------------------------------------------------------------
|
|
| 8 | - |
|
| 9 | -module GHC.Linker.ExtraObj
|
|
| 10 | - ( mkExtraObj
|
|
| 11 | - , mkExtraObjToLinkIntoBinary
|
|
| 12 | - , mkNoteObjsToLinkIntoBinary
|
|
| 13 | - , checkLinkInfo
|
|
| 14 | - , getLinkInfo
|
|
| 15 | - , ghcLinkInfoSectionName
|
|
| 16 | - , ghcLinkInfoNoteName
|
|
| 17 | - , platformSupportsSavingLinkOpts
|
|
| 18 | - , haveRtsOptsFlags
|
|
| 19 | - )
|
|
| 20 | -where
|
|
| 21 | - |
|
| 22 | -import GHC.Prelude
|
|
| 23 | -import GHC.Platform
|
|
| 24 | - |
|
| 25 | -import GHC.Unit
|
|
| 26 | -import GHC.Unit.Env
|
|
| 27 | - |
|
| 28 | -import GHC.Utils.Asm
|
|
| 29 | -import GHC.Utils.Error
|
|
| 30 | -import GHC.Utils.Misc
|
|
| 31 | -import GHC.Utils.Outputable as Outputable
|
|
| 32 | -import GHC.Utils.Logger
|
|
| 33 | -import GHC.Utils.TmpFs
|
|
| 34 | - |
|
| 35 | -import GHC.Driver.Session
|
|
| 36 | -import GHC.Driver.Ppr
|
|
| 37 | - |
|
| 38 | -import qualified GHC.Data.ShortText as ST
|
|
| 39 | - |
|
| 40 | -import GHC.SysTools.Elf
|
|
| 41 | -import GHC.SysTools.Tasks
|
|
| 42 | -import GHC.Linker.Unit
|
|
| 43 | - |
|
| 44 | -import Control.Monad
|
|
| 45 | -import Data.Maybe
|
|
| 46 | - |
|
| 47 | -mkExtraObj :: Logger -> TmpFs -> DynFlags -> UnitState -> Suffix -> String -> IO FilePath
|
|
| 48 | -mkExtraObj logger tmpfs dflags unit_state extn xs
|
|
| 49 | - = do cFile <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule extn
|
|
| 50 | - oFile <- newTempName logger tmpfs (tmpDir dflags) TFL_GhcSession "o"
|
|
| 51 | - writeFile cFile xs
|
|
| 52 | - runCc Nothing logger tmpfs dflags
|
|
| 53 | - ([Option "-c",
|
|
| 54 | - FileOption "" cFile,
|
|
| 55 | - Option "-o",
|
|
| 56 | - FileOption "" oFile]
|
|
| 57 | - ++ if extn /= "s"
|
|
| 58 | - then cOpts
|
|
| 59 | - else [])
|
|
| 60 | - return oFile
|
|
| 61 | - where
|
|
| 62 | - -- Pass a different set of options to the C compiler depending one whether
|
|
| 63 | - -- we're compiling C or assembler. When compiling C, we pass the usual
|
|
| 64 | - -- set of include directories and PIC flags.
|
|
| 65 | - cOpts = map Option (picCCOpts dflags)
|
|
| 66 | - ++ map (FileOption "-I" . ST.unpack)
|
|
| 67 | - (unitIncludeDirs $ unsafeLookupUnit unit_state rtsUnit)
|
|
| 68 | - |
|
| 69 | --- When linking a binary, we need to create a C main() function that
|
|
| 70 | --- starts everything off. This used to be compiled statically as part
|
|
| 71 | --- of the RTS, but that made it hard to change the -rtsopts setting,
|
|
| 72 | --- so now we generate and compile a main() stub as part of every
|
|
| 73 | --- binary and pass the -rtsopts setting directly to the RTS (#5373)
|
|
| 74 | ---
|
|
| 75 | --- On Windows, when making a shared library we also may need a DllMain.
|
|
| 76 | ---
|
|
| 77 | -mkExtraObjToLinkIntoBinary :: Logger -> TmpFs -> DynFlags -> UnitState -> IO (Maybe FilePath)
|
|
| 78 | -mkExtraObjToLinkIntoBinary logger tmpfs dflags unit_state = do
|
|
| 79 | - when (gopt Opt_NoHsMain dflags && haveRtsOptsFlags dflags) $
|
|
| 80 | - logInfo logger $ withPprStyle defaultUserStyle
|
|
| 81 | - (text "Warning: -rtsopts and -with-rtsopts have no effect with -no-hs-main." $$
|
|
| 82 | - text " Call hs_init_ghc() from your main() function to set these options.")
|
|
| 83 | - |
|
| 84 | - case ghcLink dflags of
|
|
| 85 | - -- Don't try to build the extra object if it is not needed. Compiling the
|
|
| 86 | - -- extra object assumes the presence of the RTS in the unit database
|
|
| 87 | - -- (because the extra object imports Rts.h) but GHC's build system may try
|
|
| 88 | - -- to build some helper programs before building and registering the RTS!
|
|
| 89 | - -- See #18938 for an example where hp2ps failed to build because of a failed
|
|
| 90 | - -- (unsafe) lookup for the RTS in the unit db.
|
|
| 91 | - _ | gopt Opt_NoHsMain dflags
|
|
| 92 | - -> return Nothing
|
|
| 93 | - |
|
| 94 | - LinkDynLib
|
|
| 95 | - | OSMinGW32 <- platformOS (targetPlatform dflags)
|
|
| 96 | - -> mk_extra_obj dllMain
|
|
| 97 | - |
|
| 98 | - | otherwise
|
|
| 99 | - -> return Nothing
|
|
| 100 | - |
|
| 101 | - _ -> mk_extra_obj exeMain
|
|
| 102 | - |
|
| 103 | - where
|
|
| 104 | - mk_extra_obj = fmap Just . mkExtraObj logger tmpfs dflags unit_state "c" . showSDoc dflags
|
|
| 105 | - |
|
| 106 | - exeMain = vcat [
|
|
| 107 | - text "#include <Rts.h>",
|
|
| 108 | - text "extern StgClosure ZCMain_main_closure;",
|
|
| 109 | - text "int main(int argc, char *argv[])",
|
|
| 110 | - char '{',
|
|
| 111 | - text " RtsConfig __conf = defaultRtsConfig;",
|
|
| 112 | - text " __conf.rts_opts_enabled = "
|
|
| 113 | - <> text (show (rtsOptsEnabled dflags)) <> semi,
|
|
| 114 | - text " __conf.rts_opts_suggestions = "
|
|
| 115 | - <> (if rtsOptsSuggestions dflags
|
|
| 116 | - then text "true"
|
|
| 117 | - else text "false") <> semi,
|
|
| 118 | - text "__conf.keep_cafs = "
|
|
| 119 | - <> (if gopt Opt_KeepCAFs dflags
|
|
| 120 | - then text "true"
|
|
| 121 | - else text "false") <> semi,
|
|
| 122 | - case rtsOpts dflags of
|
|
| 123 | - Nothing -> Outputable.empty
|
|
| 124 | - Just opts -> text " __conf.rts_opts= " <>
|
|
| 125 | - text (show opts) <> semi,
|
|
| 126 | - text " __conf.rts_hs_main = true;",
|
|
| 127 | - text " return hs_main(argc,argv,&ZCMain_main_closure,__conf);",
|
|
| 128 | - char '}',
|
|
| 129 | - char '\n' -- final newline, to keep gcc happy
|
|
| 130 | - ]
|
|
| 131 | - |
|
| 132 | - dllMain = vcat [
|
|
| 133 | - text "#include <Rts.h>",
|
|
| 134 | - text "#include <windows.h>",
|
|
| 135 | - text "#include <stdbool.h>",
|
|
| 136 | - char '\n',
|
|
| 137 | - text "bool",
|
|
| 138 | - text "WINAPI",
|
|
| 139 | - text "DllMain ( HINSTANCE hInstance STG_UNUSED",
|
|
| 140 | - text " , DWORD reason STG_UNUSED",
|
|
| 141 | - text " , LPVOID reserved STG_UNUSED",
|
|
| 142 | - text " )",
|
|
| 143 | - text "{",
|
|
| 144 | - text " return true;",
|
|
| 145 | - text "}",
|
|
| 146 | - char '\n' -- final newline, to keep gcc happy
|
|
| 147 | - ]
|
|
| 148 | - |
|
| 149 | --- Write out the link info section into a new assembly file. Previously
|
|
| 150 | --- this was included as inline assembly in the main.c file but this
|
|
| 151 | --- is pretty fragile. gas gets upset trying to calculate relative offsets
|
|
| 152 | --- that span the .note section (notably .text) when debug info is present
|
|
| 153 | -mkNoteObjsToLinkIntoBinary :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [UnitId] -> IO [FilePath]
|
|
| 154 | -mkNoteObjsToLinkIntoBinary logger tmpfs dflags unit_env dep_packages = do
|
|
| 155 | - link_info <- getLinkInfo dflags unit_env dep_packages
|
|
| 156 | - |
|
| 157 | - if (platformSupportsSavingLinkOpts (platformOS platform ))
|
|
| 158 | - then fmap (:[]) $ mkExtraObj logger tmpfs dflags unit_state "s" (showSDoc dflags (link_opts link_info))
|
|
| 159 | - else return []
|
|
| 160 | - |
|
| 161 | - where
|
|
| 162 | - unit_state = ue_homeUnitState unit_env
|
|
| 163 | - platform = ue_platform unit_env
|
|
| 164 | - link_opts info = hcat
|
|
| 165 | - [ -- "link info" section (see Note [LinkInfo section])
|
|
| 166 | - makeElfNote platform ghcLinkInfoSectionName ghcLinkInfoNoteName 0 info
|
|
| 167 | - |
|
| 168 | - -- ALL generated assembly must have this section to disable
|
|
| 169 | - -- executable stacks. See also
|
|
| 170 | - -- "GHC.CmmToAsm" for another instance
|
|
| 171 | - -- where we need to do this.
|
|
| 172 | - , if platformHasGnuNonexecStack platform
|
|
| 173 | - then text ".section .note.GNU-stack,\"\","
|
|
| 174 | - <> sectionType platform "progbits" <> char '\n'
|
|
| 175 | - else Outputable.empty
|
|
| 176 | - ]
|
|
| 177 | - |
|
| 178 | --- | Return the "link info" string
|
|
| 179 | ---
|
|
| 180 | --- See Note [LinkInfo section]
|
|
| 181 | -getLinkInfo :: DynFlags -> UnitEnv -> [UnitId] -> IO String
|
|
| 182 | -getLinkInfo dflags unit_env dep_packages = do
|
|
| 183 | - package_link_opts <- getUnitLinkOpts (ghcNameVersion dflags) (ways dflags) unit_env dep_packages
|
|
| 184 | - pkg_frameworks <- if not (platformUsesFrameworks (ue_platform unit_env))
|
|
| 185 | - then return []
|
|
| 186 | - else do
|
|
| 187 | - ps <- mayThrowUnitErr (preloadUnitsInfo' unit_env dep_packages)
|
|
| 188 | - return (collectFrameworks ps)
|
|
| 189 | - let link_info =
|
|
| 190 | - ( package_link_opts
|
|
| 191 | - , pkg_frameworks
|
|
| 192 | - , rtsOpts dflags
|
|
| 193 | - , rtsOptsEnabled dflags
|
|
| 194 | - , gopt Opt_NoHsMain dflags
|
|
| 195 | - , map showOpt (ldInputs dflags)
|
|
| 196 | - , getOpts dflags opt_l
|
|
| 197 | - )
|
|
| 198 | - return (show link_info)
|
|
| 199 | - |
|
| 200 | -platformSupportsSavingLinkOpts :: OS -> Bool
|
|
| 201 | -platformSupportsSavingLinkOpts os
|
|
| 202 | - | os == OSSolaris2 = False -- see #5382
|
|
| 203 | - | otherwise = osElfTarget os
|
|
| 204 | - |
|
| 205 | --- See Note [LinkInfo section]
|
|
| 206 | -ghcLinkInfoSectionName :: String
|
|
| 207 | -ghcLinkInfoSectionName = ".debug-ghc-link-info"
|
|
| 208 | - -- if we use the ".debug" prefix, then strip will strip it by default
|
|
| 209 | - |
|
| 210 | --- Identifier for the note (see Note [LinkInfo section])
|
|
| 211 | -ghcLinkInfoNoteName :: String
|
|
| 212 | -ghcLinkInfoNoteName = "GHC link info"
|
|
| 213 | - |
|
| 214 | --- Returns 'False' if it was, and we can avoid linking, because the
|
|
| 215 | --- previous binary was linked with "the same options".
|
|
| 216 | -checkLinkInfo :: Logger -> DynFlags -> UnitEnv -> [UnitId] -> FilePath -> IO Bool
|
|
| 217 | -checkLinkInfo logger dflags unit_env pkg_deps exe_file
|
|
| 218 | - | not (platformSupportsSavingLinkOpts (platformOS (ue_platform unit_env)))
|
|
| 219 | - -- ToDo: Windows and OS X do not use the ELF binary format, so
|
|
| 220 | - -- readelf does not work there. We need to find another way to do
|
|
| 221 | - -- this.
|
|
| 222 | - = return False -- conservatively we should return True, but not
|
|
| 223 | - -- linking in this case was the behaviour for a long
|
|
| 224 | - -- time so we leave it as-is.
|
|
| 225 | - | otherwise
|
|
| 226 | - = do
|
|
| 227 | - link_info <- getLinkInfo dflags unit_env pkg_deps
|
|
| 228 | - debugTraceMsg logger 3 $ text ("Link info: " ++ link_info)
|
|
| 229 | - m_exe_link_info <- readElfNoteAsString logger exe_file
|
|
| 230 | - ghcLinkInfoSectionName ghcLinkInfoNoteName
|
|
| 231 | - let sameLinkInfo = (Just link_info == m_exe_link_info)
|
|
| 232 | - debugTraceMsg logger 3 $ case m_exe_link_info of
|
|
| 233 | - Nothing -> text "Exe link info: Not found"
|
|
| 234 | - Just s
|
|
| 235 | - | sameLinkInfo -> text ("Exe link info is the same")
|
|
| 236 | - | otherwise -> text ("Exe link info is different: " ++ s)
|
|
| 237 | - return (not sameLinkInfo)
|
|
| 238 | - |
|
| 239 | -{- Note [LinkInfo section]
|
|
| 240 | - ~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 241 | - |
|
| 242 | -The "link info" is a string representing the parameters of the link. We save
|
|
| 243 | -this information in the binary, and the next time we link, if nothing else has
|
|
| 244 | -changed, we use the link info stored in the existing binary to decide whether
|
|
| 245 | -to re-link or not.
|
|
| 246 | - |
|
| 247 | -The "link info" string is stored in a ELF section called ".debug-ghc-link-info"
|
|
| 248 | -(see ghcLinkInfoSectionName) with the SHT_NOTE type. For some time, it used to
|
|
| 249 | -not follow the specified record-based format (see #11022).
|
|
| 250 | - |
|
| 251 | --}
|
|
| 252 | - |
|
| 253 | -haveRtsOptsFlags :: DynFlags -> Bool
|
|
| 254 | -haveRtsOptsFlags dflags =
|
|
| 255 | - isJust (rtsOpts dflags) || case rtsOptsEnabled dflags of
|
|
| 256 | - RtsOptsSafeOnly -> False
|
|
| 257 | - _ -> True |
| ... | ... | @@ -406,6 +406,7 @@ loadCmdLineLibs'' interp hsc_env pls = |
| 406 | 406 | , libraryPaths = lib_paths_base})
|
| 407 | 407 | = hsc_dflags hsc_env
|
| 408 | 408 | let logger = hsc_logger hsc_env
|
| 409 | + let ld_config = configureLd dflags
|
|
| 409 | 410 | |
| 410 | 411 | -- (c) Link libraries from the command-line
|
| 411 | 412 | let minus_ls_1 = [ lib | Option ('-':'l':lib) <- cmdline_ld_inputs ]
|
| ... | ... | @@ -421,7 +422,7 @@ loadCmdLineLibs'' interp hsc_env pls = |
| 421 | 422 | OSMinGW32 -> "pthread" : minus_ls_1
|
| 422 | 423 | _ -> minus_ls_1
|
| 423 | 424 | -- See Note [Fork/Exec Windows]
|
| 424 | - gcc_paths <- getGCCPaths logger dflags os
|
|
| 425 | + gcc_paths <- getGCCPaths logger platform ld_config
|
|
| 425 | 426 | |
| 426 | 427 | lib_paths_env <- addEnvPaths "LIBRARY_PATH" lib_paths_base
|
| 427 | 428 | |
| ... | ... | @@ -1254,6 +1255,7 @@ loadPackage interp hsc_env pkgs |
| 1254 | 1255 | = do
|
| 1255 | 1256 | let dflags = hsc_dflags hsc_env
|
| 1256 | 1257 | let logger = hsc_logger hsc_env
|
| 1258 | + ld_config = configureLd dflags
|
|
| 1257 | 1259 | platform = targetPlatform dflags
|
| 1258 | 1260 | is_dyn = interpreterDynamic interp
|
| 1259 | 1261 | dirs | is_dyn = [map ST.unpack $ Packages.unitLibraryDynDirs pkg | pkg <- pkgs]
|
| ... | ... | @@ -1281,7 +1283,7 @@ loadPackage interp hsc_env pkgs |
| 1281 | 1283 | extra_libs = zipWith (++) extdeplibs linkerlibs
|
| 1282 | 1284 | |
| 1283 | 1285 | -- See Note [Fork/Exec Windows]
|
| 1284 | - gcc_paths <- getGCCPaths logger dflags (platformOS platform)
|
|
| 1286 | + gcc_paths <- getGCCPaths logger platform ld_config
|
|
| 1285 | 1287 | dirs_env <- traverse (addEnvPaths "LIBRARY_PATH") dirs
|
| 1286 | 1288 | |
| 1287 | 1289 | hs_classifieds
|
| ... | ... | @@ -1507,6 +1509,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0 |
| 1507 | 1509 | dflags = hsc_dflags hsc_env
|
| 1508 | 1510 | logger = hsc_logger hsc_env
|
| 1509 | 1511 | diag_opts = initDiagOpts dflags
|
| 1512 | + ld_config = configureLd dflags
|
|
| 1510 | 1513 | dirs = lib_dirs ++ gcc_dirs
|
| 1511 | 1514 | gcc = False
|
| 1512 | 1515 | user = True
|
| ... | ... | @@ -1570,7 +1573,7 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0 |
| 1570 | 1573 | findSysDll = fmap (fmap $ DLL . dropExtension . takeFileName) $
|
| 1571 | 1574 | findSystemLibrary interp so_name
|
| 1572 | 1575 | #endif
|
| 1573 | - tryGcc = let search = searchForLibUsingGcc logger dflags
|
|
| 1576 | + tryGcc = let search = searchForLibUsingGcc logger ld_config
|
|
| 1574 | 1577 | #if defined(CAN_LOAD_DLL)
|
| 1575 | 1578 | dllpath = liftM (fmap DLLPath)
|
| 1576 | 1579 | short = dllpath $ search so_name lib_dirs
|
| ... | ... | @@ -1624,11 +1627,11 @@ locateLib interp hsc_env is_hs lib_dirs gcc_dirs lib0 |
| 1624 | 1627 | #endif
|
| 1625 | 1628 | os = platformOS platform
|
| 1626 | 1629 | |
| 1627 | -searchForLibUsingGcc :: Logger -> DynFlags -> String -> [FilePath] -> IO (Maybe FilePath)
|
|
| 1628 | -searchForLibUsingGcc logger dflags so dirs = do
|
|
| 1630 | +searchForLibUsingGcc :: Logger -> LdConfig -> String -> [FilePath] -> IO (Maybe FilePath)
|
|
| 1631 | +searchForLibUsingGcc logger ld_config so dirs = do
|
|
| 1629 | 1632 | -- GCC does not seem to extend the library search path (using -L) when using
|
| 1630 | 1633 | -- --print-file-name. So instead pass it a new base location.
|
| 1631 | - str <- askLd logger dflags (map (FileOption "-B") dirs
|
|
| 1634 | + str <- askLd logger ld_config (map (FileOption "-B") dirs
|
|
| 1632 | 1635 | ++ [Option "--print-file-name", Option so])
|
| 1633 | 1636 | let file = case lines str of
|
| 1634 | 1637 | [] -> ""
|
| ... | ... | @@ -1640,10 +1643,10 @@ searchForLibUsingGcc logger dflags so dirs = do |
| 1640 | 1643 | |
| 1641 | 1644 | -- | Retrieve the list of search directory GCC and the System use to find
|
| 1642 | 1645 | -- libraries and components. See Note [Fork/Exec Windows].
|
| 1643 | -getGCCPaths :: Logger -> DynFlags -> OS -> IO [FilePath]
|
|
| 1644 | -getGCCPaths logger dflags os
|
|
| 1645 | - | os == OSMinGW32 || platformArch (targetPlatform dflags) == ArchWasm32 =
|
|
| 1646 | - do gcc_dirs <- getGccSearchDirectory logger dflags "libraries"
|
|
| 1646 | +getGCCPaths :: Logger -> Platform -> LdConfig -> IO [FilePath]
|
|
| 1647 | +getGCCPaths logger platform ld_config
|
|
| 1648 | + | platformOS platform == OSMinGW32 || platformArch platform == ArchWasm32 =
|
|
| 1649 | + do gcc_dirs <- getGccSearchDirectory logger ld_config "libraries"
|
|
| 1647 | 1650 | sys_dirs <- getSystemDirectories
|
| 1648 | 1651 | return $ nub $ gcc_dirs ++ sys_dirs
|
| 1649 | 1652 | | otherwise = return []
|
| ... | ... | @@ -1663,8 +1666,8 @@ gccSearchDirCache = unsafePerformIO $ newIORef [] |
| 1663 | 1666 | -- which hopefully is written in an optimized manner to take advantage of
|
| 1664 | 1667 | -- caching. At the very least we remove the overhead of the fork/exec and waits
|
| 1665 | 1668 | -- which dominate a large percentage of startup time on Windows.
|
| 1666 | -getGccSearchDirectory :: Logger -> DynFlags -> String -> IO [FilePath]
|
|
| 1667 | -getGccSearchDirectory logger dflags key = do
|
|
| 1669 | +getGccSearchDirectory :: Logger -> LdConfig -> String -> IO [FilePath]
|
|
| 1670 | +getGccSearchDirectory logger ld_config key = do
|
|
| 1668 | 1671 | #if defined(wasm32_HOST_ARCH)
|
| 1669 | 1672 | pure []
|
| 1670 | 1673 | #else
|
| ... | ... | @@ -1672,7 +1675,7 @@ getGccSearchDirectory logger dflags key = do |
| 1672 | 1675 | case lookup key cache of
|
| 1673 | 1676 | Just x -> return x
|
| 1674 | 1677 | Nothing -> do
|
| 1675 | - str <- askLd logger dflags [Option "--print-search-dirs"]
|
|
| 1678 | + str <- askLd logger ld_config [Option "--print-search-dirs"]
|
|
| 1676 | 1679 | let line = dropWhile isSpace str
|
| 1677 | 1680 | name = key ++ ": ="
|
| 1678 | 1681 | if null line
|
| ... | ... | @@ -17,7 +17,6 @@ import GHC.Unit.Types |
| 17 | 17 | import GHC.Unit.State
|
| 18 | 18 | import GHC.Unit.Env
|
| 19 | 19 | |
| 20 | -import GHC.Settings
|
|
| 21 | 20 | import GHC.SysTools.Tasks
|
| 22 | 21 | |
| 23 | 22 | import GHC.Runtime.Interpreter
|
| ... | ... | @@ -49,13 +48,13 @@ import Text.ParserCombinators.ReadP as Parser |
| 49 | 48 | -- dynamic library through @-add_rpath@.
|
| 50 | 49 | --
|
| 51 | 50 | -- See Note [Dynamic linking on macOS]
|
| 52 | -runInjectRPaths :: Logger -> ToolSettings -> [FilePath] -> FilePath -> IO ()
|
|
| 53 | -runInjectRPaths logger toolSettings lib_paths dylib = do
|
|
| 54 | - info <- lines <$> askOtool logger toolSettings Nothing [Option "-L", Option dylib]
|
|
| 51 | +runInjectRPaths :: Logger -> OtoolConfig -> InstallNameConfig -> [FilePath] -> FilePath -> IO ()
|
|
| 52 | +runInjectRPaths logger otool_opts install_name_opts lib_paths dylib = do
|
|
| 53 | + info <- lines <$> askOtool logger otool_opts Nothing [Option "-L", Option dylib]
|
|
| 55 | 54 | -- filter the output for only the libraries. And then drop the @rpath prefix.
|
| 56 | 55 | let libs = fmap (drop 7) $ filter (isPrefixOf "@rpath") $ fmap (head.words) $ info
|
| 57 | 56 | -- find any pre-existing LC_PATH items
|
| 58 | - info <- lines <$> askOtool logger toolSettings Nothing [Option "-l", Option dylib]
|
|
| 57 | + info <- lines <$> askOtool logger otool_opts Nothing [Option "-l", Option dylib]
|
|
| 59 | 58 | let paths = mapMaybe get_rpath info
|
| 60 | 59 | lib_paths' = [ p | p <- lib_paths, not (p `elem` paths) ]
|
| 61 | 60 | -- only find those rpaths, that aren't already in the library.
|
| ... | ... | @@ -63,7 +62,7 @@ runInjectRPaths logger toolSettings lib_paths dylib = do |
| 63 | 62 | -- inject the rpaths
|
| 64 | 63 | case rpaths of
|
| 65 | 64 | [] -> return ()
|
| 66 | - _ -> runInstallNameTool logger toolSettings $ map Option $ "-add_rpath":(intersperse "-add_rpath" rpaths) ++ [dylib]
|
|
| 65 | + _ -> runInstallNameTool logger install_name_opts $ map Option $ "-add_rpath":(intersperse "-add_rpath" rpaths) ++ [dylib]
|
|
| 67 | 66 | |
| 68 | 67 | get_rpath :: String -> Maybe FilePath
|
| 69 | 68 | get_rpath l = case readP_to_S rpath_parser l of
|
| 1 | 1 | module GHC.Linker.Static
|
| 2 | - ( linkBinary
|
|
| 3 | - , linkStaticLib
|
|
| 2 | + ( linkStaticLib
|
|
| 4 | 3 | )
|
| 5 | 4 | where
|
| 6 | 5 | |
| 7 | 6 | import GHC.Prelude
|
| 8 | 7 | import GHC.Platform
|
| 9 | -import GHC.Platform.Ways
|
|
| 10 | 8 | import GHC.Settings
|
| 11 | 9 | |
| 12 | 10 | import GHC.SysTools
|
| ... | ... | @@ -19,24 +17,15 @@ import GHC.Unit.State |
| 19 | 17 | |
| 20 | 18 | import GHC.Utils.Logger
|
| 21 | 19 | import GHC.Utils.Monad
|
| 22 | -import GHC.Utils.Misc
|
|
| 23 | -import GHC.Utils.TmpFs
|
|
| 24 | 20 | |
| 25 | -import GHC.Linker.MacOS
|
|
| 26 | 21 | import GHC.Linker.Unit
|
| 27 | -import GHC.Linker.Dynamic
|
|
| 28 | -import GHC.Linker.ExtraObj
|
|
| 29 | -import GHC.Linker.External
|
|
| 30 | -import GHC.Linker.Windows
|
|
| 31 | 22 | import GHC.Linker.Static.Utils
|
| 32 | 23 | |
| 33 | -import GHC.Driver.Config.Linker
|
|
| 34 | 24 | import GHC.Driver.Session
|
| 35 | 25 | |
| 36 | 26 | import System.FilePath
|
| 37 | 27 | import System.Directory
|
| 38 | 28 | import Control.Monad
|
| 39 | -import Data.Maybe
|
|
| 40 | 29 | |
| 41 | 30 | -----------------------------------------------------------------------------
|
| 42 | 31 | -- Static linking, of .o files
|
| ... | ... | @@ -51,225 +40,6 @@ import Data.Maybe |
| 51 | 40 | -- read any interface files), so the user must explicitly specify all
|
| 52 | 41 | -- the packages.
|
| 53 | 42 | |
| 54 | -{-
|
|
| 55 | -Note [-Xlinker -rpath vs -Wl,-rpath]
|
|
| 56 | -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 57 | - |
|
| 58 | --Wl takes a comma-separated list of options which in the case of
|
|
| 59 | --Wl,-rpath -Wl,some,path,with,commas parses the path with commas
|
|
| 60 | -as separate options.
|
|
| 61 | -Buck, the build system, produces paths with commas in them.
|
|
| 62 | - |
|
| 63 | --Xlinker doesn't have this disadvantage and as far as I can tell
|
|
| 64 | -it is supported by both gcc and clang. Anecdotally nvcc supports
|
|
| 65 | --Xlinker, but not -Wl.
|
|
| 66 | --}
|
|
| 67 | - |
|
| 68 | -linkBinary :: Logger -> TmpFs -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO ()
|
|
| 69 | -linkBinary = linkBinary' False
|
|
| 70 | - |
|
| 71 | -linkBinary' :: Bool -> Logger -> TmpFs -> DynFlags -> UnitEnv -> [FilePath] -> [UnitId] -> IO ()
|
|
| 72 | -linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do
|
|
| 73 | - let platform = ue_platform unit_env
|
|
| 74 | - unit_state = ue_homeUnitState unit_env
|
|
| 75 | - toolSettings' = toolSettings dflags
|
|
| 76 | - verbFlags = getVerbFlags dflags
|
|
| 77 | - arch_os = platformArchOS platform
|
|
| 78 | - output_fn = exeFileName arch_os staticLink (outputFile_ dflags)
|
|
| 79 | - namever = ghcNameVersion dflags
|
|
| 80 | - -- For the wasm target, when ghc is invoked with -dynamic,
|
|
| 81 | - -- when linking the final .wasm binary we must still ensure
|
|
| 82 | - -- the static archives are selected. Otherwise wasm-ld would
|
|
| 83 | - -- fail to find and link the .so library dependencies. wasm-ld
|
|
| 84 | - -- can link PIC objects into static .wasm binaries fine, so we
|
|
| 85 | - -- only adjust the ways in the final linking step, and only
|
|
| 86 | - -- when linking .wasm binary (which is supposed to be fully
|
|
| 87 | - -- static), not when linking .so shared libraries.
|
|
| 88 | - ways_
|
|
| 89 | - | ArchWasm32 <- platformArch platform = removeWay WayDyn $ targetWays_ dflags
|
|
| 90 | - | otherwise = ways dflags
|
|
| 91 | - |
|
| 92 | - full_output_fn <- if isAbsolute output_fn
|
|
| 93 | - then return output_fn
|
|
| 94 | - else do d <- getCurrentDirectory
|
|
| 95 | - return $ normalise (d </> output_fn)
|
|
| 96 | - |
|
| 97 | - -- get the full list of packages to link with, by combining the
|
|
| 98 | - -- explicit packages with the auto packages and all of their
|
|
| 99 | - -- dependencies, and eliminating duplicates.
|
|
| 100 | - pkgs <- mayThrowUnitErr (preloadUnitsInfo' unit_env dep_units)
|
|
| 101 | - let pkg_lib_paths = collectLibraryDirs ways_ pkgs
|
|
| 102 | - let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
|
|
| 103 | - get_pkg_lib_path_opts l
|
|
| 104 | - | osElfTarget (platformOS platform) &&
|
|
| 105 | - dynLibLoader dflags == SystemDependent &&
|
|
| 106 | - ways_ `hasWay` WayDyn
|
|
| 107 | - = let libpath = if gopt Opt_RelativeDynlibPaths dflags
|
|
| 108 | - then "$ORIGIN" </>
|
|
| 109 | - (l `makeRelativeTo` full_output_fn)
|
|
| 110 | - else l
|
|
| 111 | - -- See Note [-Xlinker -rpath vs -Wl,-rpath]
|
|
| 112 | - rpath = if useXLinkerRPath dflags (platformOS platform)
|
|
| 113 | - then ["-Xlinker", "-rpath", "-Xlinker", libpath]
|
|
| 114 | - else []
|
|
| 115 | - -- Solaris 11's linker does not support -rpath-link option. It silently
|
|
| 116 | - -- ignores it and then complains about next option which is -l<some
|
|
| 117 | - -- dir> as being a directory and not expected object file, E.g
|
|
| 118 | - -- ld: elf error: file
|
|
| 119 | - -- /tmp/ghc-src/libraries/base/dist-install/build:
|
|
| 120 | - -- elf_begin: I/O error: region read: Is a directory
|
|
| 121 | - rpathlink = if (platformOS platform) == OSSolaris2
|
|
| 122 | - then []
|
|
| 123 | - else ["-Xlinker", "-rpath-link", "-Xlinker", l]
|
|
| 124 | - in ["-L" ++ l] ++ rpathlink ++ rpath
|
|
| 125 | - | osMachOTarget (platformOS platform) &&
|
|
| 126 | - dynLibLoader dflags == SystemDependent &&
|
|
| 127 | - ways_ `hasWay` WayDyn &&
|
|
| 128 | - useXLinkerRPath dflags (platformOS platform)
|
|
| 129 | - = let libpath = if gopt Opt_RelativeDynlibPaths dflags
|
|
| 130 | - then "@loader_path" </>
|
|
| 131 | - (l `makeRelativeTo` full_output_fn)
|
|
| 132 | - else l
|
|
| 133 | - in ["-L" ++ l] ++ ["-Xlinker", "-rpath", "-Xlinker", libpath]
|
|
| 134 | - | otherwise = ["-L" ++ l]
|
|
| 135 | - |
|
| 136 | - pkg_lib_path_opts <-
|
|
| 137 | - if gopt Opt_SingleLibFolder dflags
|
|
| 138 | - then do
|
|
| 139 | - libs <- getLibs namever ways_ unit_env dep_units
|
|
| 140 | - tmpDir <- newTempSubDir logger tmpfs (tmpDir dflags)
|
|
| 141 | - sequence_ [ copyFile lib (tmpDir </> basename)
|
|
| 142 | - | (lib, basename) <- libs]
|
|
| 143 | - return [ "-L" ++ tmpDir ]
|
|
| 144 | - else pure pkg_lib_path_opts
|
|
| 145 | - |
|
| 146 | - let
|
|
| 147 | - dead_strip
|
|
| 148 | - | gopt Opt_WholeArchiveHsLibs dflags = []
|
|
| 149 | - | otherwise = if osSubsectionsViaSymbols (platformOS platform)
|
|
| 150 | - then ["-Wl,-dead_strip"]
|
|
| 151 | - else []
|
|
| 152 | - let lib_paths = libraryPaths dflags
|
|
| 153 | - let lib_path_opts = map ("-L"++) lib_paths
|
|
| 154 | - |
|
| 155 | - extraLinkObj <- maybeToList <$> mkExtraObjToLinkIntoBinary logger tmpfs dflags unit_state
|
|
| 156 | - noteLinkObjs <- mkNoteObjsToLinkIntoBinary logger tmpfs dflags unit_env dep_units
|
|
| 157 | - |
|
| 158 | - let
|
|
| 159 | - (pre_hs_libs, post_hs_libs)
|
|
| 160 | - | gopt Opt_WholeArchiveHsLibs dflags
|
|
| 161 | - = if platformOS platform == OSDarwin
|
|
| 162 | - then (["-Wl,-all_load"], [])
|
|
| 163 | - -- OS X does not have a flag to turn off -all_load
|
|
| 164 | - else (["-Wl,--whole-archive"], ["-Wl,--no-whole-archive"])
|
|
| 165 | - | otherwise
|
|
| 166 | - = ([],[])
|
|
| 167 | - |
|
| 168 | - pkg_link_opts <- do
|
|
| 169 | - unit_link_opts <- getUnitLinkOpts namever ways_ unit_env dep_units
|
|
| 170 | - return $ otherFlags unit_link_opts ++ dead_strip
|
|
| 171 | - ++ pre_hs_libs ++ hsLibs unit_link_opts ++ post_hs_libs
|
|
| 172 | - ++ extraLibs unit_link_opts
|
|
| 173 | - -- -Wl,-u,<sym> contained in other_flags
|
|
| 174 | - -- needs to be put before -l<package>,
|
|
| 175 | - -- otherwise Solaris linker fails linking
|
|
| 176 | - -- a binary with unresolved symbols in RTS
|
|
| 177 | - -- which are defined in base package
|
|
| 178 | - -- the reason for this is a note in ld(1) about
|
|
| 179 | - -- '-u' option: "The placement of this option
|
|
| 180 | - -- on the command line is significant.
|
|
| 181 | - -- This option must be placed before the library
|
|
| 182 | - -- that defines the symbol."
|
|
| 183 | - |
|
| 184 | - -- frameworks
|
|
| 185 | - pkg_framework_opts <- getUnitFrameworkOpts unit_env dep_units
|
|
| 186 | - let framework_opts = getFrameworkOpts (initFrameworkOpts dflags) platform
|
|
| 187 | - |
|
| 188 | - -- probably _stub.o files
|
|
| 189 | - let extra_ld_inputs = ldInputs dflags
|
|
| 190 | - |
|
| 191 | - rc_objs <- case platformOS platform of
|
|
| 192 | - OSMinGW32 | gopt Opt_GenManifest dflags -> maybeCreateManifest logger tmpfs dflags output_fn
|
|
| 193 | - _ -> return []
|
|
| 194 | - |
|
| 195 | - let linker_config = initLinkerConfig dflags
|
|
| 196 | - let link dflags args = do
|
|
| 197 | - runLink logger tmpfs linker_config args
|
|
| 198 | - -- Make sure to honour -fno-use-rpaths if set on darwin as well; see #20004
|
|
| 199 | - when (platformOS platform == OSDarwin && gopt Opt_RPath dflags) $
|
|
| 200 | - GHC.Linker.MacOS.runInjectRPaths logger (toolSettings dflags) pkg_lib_paths output_fn
|
|
| 201 | - |
|
| 202 | - link dflags (
|
|
| 203 | - map GHC.SysTools.Option verbFlags
|
|
| 204 | - ++ [ GHC.SysTools.Option "-o"
|
|
| 205 | - , GHC.SysTools.FileOption "" output_fn
|
|
| 206 | - ]
|
|
| 207 | - ++ libmLinkOpts platform
|
|
| 208 | - ++ map GHC.SysTools.Option (
|
|
| 209 | - []
|
|
| 210 | - |
|
| 211 | - -- See Note [No PIE when linking]
|
|
| 212 | - ++ pieCCLDOpts dflags
|
|
| 213 | - |
|
| 214 | - -- Permit the linker to auto link _symbol to _imp_symbol.
|
|
| 215 | - -- This lets us link against DLLs without needing an "import library".
|
|
| 216 | - ++ (if platformOS platform == OSMinGW32
|
|
| 217 | - then ["-Wl,--enable-auto-import"]
|
|
| 218 | - else [])
|
|
| 219 | - |
|
| 220 | - -- '-no_compact_unwind'
|
|
| 221 | - -- C++/Objective-C exceptions cannot use optimised
|
|
| 222 | - -- stack unwinding code. The optimised form is the
|
|
| 223 | - -- default in Xcode 4 on at least x86_64, and
|
|
| 224 | - -- without this flag we're also seeing warnings
|
|
| 225 | - -- like
|
|
| 226 | - -- ld: warning: could not create compact unwind for .LFB3: non-standard register 5 being saved in prolog
|
|
| 227 | - -- on x86.
|
|
| 228 | - ++ (if not (gopt Opt_CompactUnwind dflags) &&
|
|
| 229 | - toolSettings_ldSupportsCompactUnwind toolSettings' &&
|
|
| 230 | - (platformOS platform == OSDarwin) &&
|
|
| 231 | - case platformArch platform of
|
|
| 232 | - ArchX86_64 -> True
|
|
| 233 | - ArchAArch64 -> True
|
|
| 234 | - _ -> False
|
|
| 235 | - then ["-Wl,-no_compact_unwind"]
|
|
| 236 | - else [])
|
|
| 237 | - |
|
| 238 | - -- We should rather be asking does it support --gc-sections?
|
|
| 239 | - ++ (if toolSettings_ldIsGnuLd toolSettings' &&
|
|
| 240 | - not (gopt Opt_WholeArchiveHsLibs dflags)
|
|
| 241 | - then ["-Wl,--gc-sections"]
|
|
| 242 | - else [])
|
|
| 243 | - |
|
| 244 | - ++ o_files
|
|
| 245 | - ++ lib_path_opts)
|
|
| 246 | - ++ extra_ld_inputs
|
|
| 247 | - ++ map GHC.SysTools.Option (
|
|
| 248 | - rc_objs
|
|
| 249 | - ++ framework_opts
|
|
| 250 | - ++ pkg_lib_path_opts
|
|
| 251 | - ++ extraLinkObj
|
|
| 252 | - ++ noteLinkObjs
|
|
| 253 | - -- See Note [RTS/ghc-internal interface]
|
|
| 254 | - -- (-u<sym> must come before -lghc-internal...!)
|
|
| 255 | - ++ (if ghcInternalUnitId `elem` map unitId pkgs
|
|
| 256 | - then [concat [ "-Wl,-u,"
|
|
| 257 | - , ['_' | platformLeadingUnderscore platform]
|
|
| 258 | - , "init_ghc_hs_iface" ]]
|
|
| 259 | - else [])
|
|
| 260 | - ++ pkg_link_opts
|
|
| 261 | - ++ pkg_framework_opts
|
|
| 262 | - ++ (if platformOS platform == OSDarwin
|
|
| 263 | - -- dead_strip_dylibs, will remove unused dylibs, and thus save
|
|
| 264 | - -- space in the load commands. The -headerpad is necessary so
|
|
| 265 | - -- that we can inject more @rpath's later for the left over
|
|
| 266 | - -- libraries during runInjectRpaths phase.
|
|
| 267 | - --
|
|
| 268 | - -- See Note [Dynamic linking on macOS].
|
|
| 269 | - then [ "-Wl,-dead_strip_dylibs", "-Wl,-headerpad,8000" ]
|
|
| 270 | - else [])
|
|
| 271 | - ))
|
|
| 272 | - |
|
| 273 | 43 | -- | Linking a static lib will not really link anything. It will merely produce
|
| 274 | 44 | -- a static archive of all dependent static libraries. The resulting library
|
| 275 | 45 | -- will still need to be linked with any remaining link flags.
|
| ... | ... | @@ -309,4 +79,5 @@ linkStaticLib logger dflags unit_env o_files dep_units = do |
| 309 | 79 | else writeBSDAr output_fn $ afilter (not . isBSDSymdef) ar
|
| 310 | 80 | |
| 311 | 81 | -- run ranlib over the archive. write*Ar does *not* create the symbol index.
|
| 312 | - runRanlib logger dflags [GHC.SysTools.FileOption "" output_fn] |
|
| 82 | + let ranlib_opts = configureRanlib dflags
|
|
| 83 | + runRanlib logger ranlib_opts [GHC.SysTools.FileOption "" output_fn] |
| 1 | 1 | module GHC.Linker.Windows
|
| 2 | - ( maybeCreateManifest
|
|
| 2 | + ( ManifestOpts (..)
|
|
| 3 | + , initManifestOpts
|
|
| 4 | + , maybeCreateManifest
|
|
| 3 | 5 | )
|
| 4 | 6 | where
|
| 5 | 7 | |
| ... | ... | @@ -12,13 +14,28 @@ import GHC.Utils.Logger |
| 12 | 14 | import System.FilePath
|
| 13 | 15 | import System.Directory
|
| 14 | 16 | |
| 17 | +data ManifestOpts = ManifestOpts
|
|
| 18 | + { manifestEmbed :: !Bool -- ^ Should the manifest be embedded in the binary with Windres
|
|
| 19 | + , manifestTempdir :: TempDir
|
|
| 20 | + , manifestWindresConfig :: WindresConfig
|
|
| 21 | + , manifestObjectSuf :: String
|
|
| 22 | + }
|
|
| 23 | + |
|
| 24 | +initManifestOpts :: DynFlags -> ManifestOpts
|
|
| 25 | +initManifestOpts dflags = ManifestOpts
|
|
| 26 | + { manifestEmbed = gopt Opt_EmbedManifest dflags
|
|
| 27 | + , manifestTempdir = tmpDir dflags
|
|
| 28 | + , manifestWindresConfig = configureWindres dflags
|
|
| 29 | + , manifestObjectSuf = objectSuf dflags
|
|
| 30 | + }
|
|
| 31 | + |
|
| 15 | 32 | maybeCreateManifest
|
| 16 | 33 | :: Logger
|
| 17 | 34 | -> TmpFs
|
| 18 | - -> DynFlags
|
|
| 35 | + -> ManifestOpts
|
|
| 19 | 36 | -> FilePath -- ^ filename of executable
|
| 20 | 37 | -> IO [FilePath] -- ^ extra objects to embed, maybe
|
| 21 | -maybeCreateManifest logger tmpfs dflags exe_filename = do
|
|
| 38 | +maybeCreateManifest logger tmpfs opts exe_filename = do
|
|
| 22 | 39 | let manifest_filename = exe_filename <.> "manifest"
|
| 23 | 40 | manifest =
|
| 24 | 41 | "<?xml version=\"1.0\" encoding=\"UTF-8\" standalone=\"yes\"?>\n\
|
| ... | ... | @@ -42,18 +59,18 @@ maybeCreateManifest logger tmpfs dflags exe_filename = do |
| 42 | 59 | -- foo.exe.manifest. However, for extra robustness, and so that
|
| 43 | 60 | -- we can move the binary around, we can embed the manifest in
|
| 44 | 61 | -- the binary itself using windres:
|
| 45 | - if not (gopt Opt_EmbedManifest dflags)
|
|
| 62 | + if not (manifestEmbed opts)
|
|
| 46 | 63 | then return []
|
| 47 | 64 | else do
|
| 48 | - rc_filename <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "rc"
|
|
| 65 | + rc_filename <- newTempName logger tmpfs (manifestTempdir opts) TFL_CurrentModule "rc"
|
|
| 49 | 66 | rc_obj_filename <-
|
| 50 | - newTempName logger tmpfs (tmpDir dflags) TFL_GhcSession (objectSuf dflags)
|
|
| 67 | + newTempName logger tmpfs (manifestTempdir opts) TFL_GhcSession (manifestObjectSuf opts)
|
|
| 51 | 68 | |
| 52 | 69 | writeFile rc_filename $
|
| 53 | 70 | "1 24 MOVEABLE PURE \"" ++ manifest_filename ++ "\"\n"
|
| 54 | 71 | -- magic numbers :-)
|
| 55 | 72 | |
| 56 | - runWindres logger dflags $ map GHC.SysTools.Option $
|
|
| 73 | + runWindres logger (manifestWindresConfig opts) $ map GHC.SysTools.Option $
|
|
| 57 | 74 | ["--input="++rc_filename,
|
| 58 | 75 | "--output="++rc_obj_filename,
|
| 59 | 76 | "--output-format=coff"]
|
| 1 | +{-# LANGUAGE MultiWayIf #-}
|
|
| 2 | + |
|
| 3 | +-- | External interpreter program
|
|
| 4 | +module GHC.Runtime.Interpreter.C
|
|
| 5 | + ( generateIservC
|
|
| 6 | + )
|
|
| 7 | +where
|
|
| 8 | + |
|
| 9 | +import GHC.Prelude
|
|
| 10 | +import GHC.Platform
|
|
| 11 | +import GHC.Data.FastString
|
|
| 12 | +import GHC.Utils.Logger
|
|
| 13 | +import GHC.Utils.TmpFs
|
|
| 14 | +import GHC.Unit.Types
|
|
| 15 | +import GHC.Unit.Env
|
|
| 16 | +import GHC.Unit.Info
|
|
| 17 | +import GHC.Unit.State
|
|
| 18 | +import GHC.Utils.Panic.Plain
|
|
| 19 | +import GHC.Linker.Executable
|
|
| 20 | +import GHC.Linker.Config
|
|
| 21 | +import GHC.Utils.CliOption
|
|
| 22 | + |
|
| 23 | +-- | Generate iserv program for the target
|
|
| 24 | +generateIservC :: Logger -> TmpFs -> ExecutableLinkOpts -> UnitEnv -> IO FilePath
|
|
| 25 | +generateIservC logger tmpfs opts unit_env = do
|
|
| 26 | + -- get the unit-id of the ghci package. We need this to load the
|
|
| 27 | + -- interpreter code.
|
|
| 28 | + let unit_state = ue_homeUnitState unit_env
|
|
| 29 | + ghci_unit_id <- case lookupPackageName unit_state (PackageName (fsLit "ghci")) of
|
|
| 30 | + Nothing -> cmdLineErrorIO "C interpreter: couldn't find \"ghci\" package"
|
|
| 31 | + Just i -> pure i
|
|
| 32 | + |
|
| 33 | + -- generate a temporary name for the iserv program
|
|
| 34 | + let tmpdir = leTempDir opts
|
|
| 35 | + exe_file <- newTempName logger tmpfs tmpdir TFL_GhcSession "iserv"
|
|
| 36 | + |
|
| 37 | + let platform = ue_platform unit_env
|
|
| 38 | + let os = platformOS platform
|
|
| 39 | + |
|
| 40 | + -- we inherit ExecutableLinkOpts for the target code (i.e. derived from
|
|
| 41 | + -- DynFlags specified by the user and from settings). We need to adjust these
|
|
| 42 | + -- options to generate the iserv program we want. Some settings are to be
|
|
| 43 | + -- shared (e.g. ways, platform, etc.) but some other must be set specifically
|
|
| 44 | + -- for iserv.
|
|
| 45 | + let opts' = opts
|
|
| 46 | + { -- write iserv program in some temporary directory
|
|
| 47 | + leOutputFile = Just exe_file
|
|
| 48 | + |
|
| 49 | + -- we need GHC to generate a main entry point...
|
|
| 50 | + , leNoHsMain = False
|
|
| 51 | + |
|
| 52 | + -- ...however the main symbol must be the iserv server
|
|
| 53 | + , leMainSymbol = zString (zEncodeFS (unitIdFS ghci_unit_id)) ++ "_GHCiziServer_defaultServer"
|
|
| 54 | + |
|
| 55 | + -- we need to reset inputs, otherwise one of them may be defining
|
|
| 56 | + -- `main` too (with -no-hs-main).
|
|
| 57 | + , leInputs = []
|
|
| 58 | + |
|
| 59 | + -- we never know what symbols GHC will look up in the future, so we
|
|
| 60 | + -- must retain CAFs for running interpreted code.
|
|
| 61 | + , leKeepCafs = True
|
|
| 62 | + |
|
| 63 | + -- enable all rts options
|
|
| 64 | + , leRtsOptsEnabled = RtsOptsAll
|
|
| 65 | + |
|
| 66 | + -- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that
|
|
| 67 | + -- refer to the RTS. This is harmless if you don't use it (adds a bit
|
|
| 68 | + -- of overhead to startup and increases the binary sizes) but if you
|
|
| 69 | + -- need it there's no alternative.
|
|
| 70 | + --
|
|
| 71 | + -- The Solaris linker does not support --export-dynamic option. It also
|
|
| 72 | + -- does not need it since it exports all dynamic symbols by default
|
|
| 73 | + , leLinkerConfig = if
|
|
| 74 | + | osElfTarget os
|
|
| 75 | + , os /= OSFreeBSD
|
|
| 76 | + , os /= OSSolaris2
|
|
| 77 | + -> (leLinkerConfig opts)
|
|
| 78 | + { linkerOptionsPost = linkerOptionsPost (leLinkerConfig opts) ++ [Option "-Wl,--export-dynamic"]
|
|
| 79 | + }
|
|
| 80 | + | otherwise
|
|
| 81 | + -> leLinkerConfig opts
|
|
| 82 | + }
|
|
| 83 | + linkExecutable logger tmpfs opts' unit_env [] [ghci_unit_id]
|
|
| 84 | + |
|
| 85 | + pure exe_file |
| 1 | +{-# LANGUAGE CPP #-}
|
|
| 2 | +{-# LANGUAGE MultiWayIf #-}
|
|
| 3 | + |
|
| 4 | +module GHC.Runtime.Interpreter.Init
|
|
| 5 | + ( initInterpreter
|
|
| 6 | + , InterpOpts (..)
|
|
| 7 | + )
|
|
| 8 | +where
|
|
| 9 | + |
|
| 10 | + |
|
| 11 | +import GHC.Prelude
|
|
| 12 | +import GHC.Platform
|
|
| 13 | +import GHC.Platform.Ways
|
|
| 14 | +import GHC.Settings
|
|
| 15 | +import GHC.Unit.Finder
|
|
| 16 | +import GHC.Unit.Env
|
|
| 17 | +import GHC.Utils.TmpFs
|
|
| 18 | +import GHC.SysTools.Tasks
|
|
| 19 | + |
|
| 20 | +import GHC.Linker.Executable
|
|
| 21 | +import qualified GHC.Linker.Loader as Loader
|
|
| 22 | +import GHC.Runtime.Interpreter
|
|
| 23 | +import GHC.Runtime.Interpreter.C
|
|
| 24 | +import GHC.StgToJS.Types (StgToJSConfig)
|
|
| 25 | + |
|
| 26 | +import GHC.Utils.Monad
|
|
| 27 | +import GHC.Utils.Outputable
|
|
| 28 | +import GHC.Utils.Logger
|
|
| 29 | +import GHC.Utils.Error
|
|
| 30 | +import Control.Concurrent
|
|
| 31 | +import System.Process
|
|
| 32 | + |
|
| 33 | +data InterpOpts = InterpOpts
|
|
| 34 | + { interpExternal :: !Bool
|
|
| 35 | + , interpProg :: String
|
|
| 36 | + , interpOpts :: [String]
|
|
| 37 | + , interpWays :: Ways
|
|
| 38 | + , interpNameVer :: GhcNameVersion
|
|
| 39 | + , interpLdConfig :: LdConfig
|
|
| 40 | + , interpCcConfig :: CcConfig
|
|
| 41 | + , interpJsInterp :: FilePath
|
|
| 42 | + , interpTmpDir :: TempDir
|
|
| 43 | + , interpFinderOpts :: FinderOpts
|
|
| 44 | + , interpJsCodegenCfg :: StgToJSConfig
|
|
| 45 | + , interpVerbosity :: Int
|
|
| 46 | + , interpCreateProcess :: Maybe (CreateProcess -> IO ProcessHandle) -- create iserv process hook
|
|
| 47 | + , interpWasmDyld :: FilePath
|
|
| 48 | + , interpBrowser :: Bool
|
|
| 49 | + , interpBrowserHost :: String
|
|
| 50 | + , interpBrowserPort :: Int
|
|
| 51 | + , interpBrowserRedirectWasiConsole :: Bool
|
|
| 52 | + , interpBrowserPuppeteerLaunchOpts :: Maybe String
|
|
| 53 | + , interpBrowserPlaywrightBrowserType :: Maybe String
|
|
| 54 | + , interpBrowserPlaywrightLaunchOpts :: Maybe String
|
|
| 55 | + , interpExecutableLinkOpts :: ExecutableLinkOpts
|
|
| 56 | + }
|
|
| 57 | + |
|
| 58 | +-- | Initialize code interpreter
|
|
| 59 | +initInterpreter
|
|
| 60 | + :: TmpFs
|
|
| 61 | + -> Logger
|
|
| 62 | + -> Platform
|
|
| 63 | + -> FinderCache
|
|
| 64 | + -> UnitEnv
|
|
| 65 | + -> InterpOpts
|
|
| 66 | + -> IO (Maybe Interp)
|
|
| 67 | +initInterpreter tmpfs logger platform finder_cache unit_env opts = do
|
|
| 68 | + |
|
| 69 | + lookup_cache <- liftIO $ mkInterpSymbolCache
|
|
| 70 | + |
|
| 71 | + -- see Note [Target code interpreter]
|
|
| 72 | + if
|
|
| 73 | +#if !defined(wasm32_HOST_ARCH)
|
|
| 74 | + -- Wasm dynamic linker
|
|
| 75 | + | ArchWasm32 <- platformArch platform
|
|
| 76 | + -> do
|
|
| 77 | + s <- liftIO $ newMVar InterpPending
|
|
| 78 | + loader <- liftIO Loader.uninitializedLoader
|
|
| 79 | + libdir <- liftIO $ last <$> Loader.getGccSearchDirectory logger (interpLdConfig opts) "libraries"
|
|
| 80 | + let profiled = interpWays opts `hasWay` WayProf
|
|
| 81 | + way_tag = if profiled then "_p" else ""
|
|
| 82 | + let cfg =
|
|
| 83 | + WasmInterpConfig
|
|
| 84 | + { wasmInterpDyLD = interpWasmDyld opts
|
|
| 85 | + , wasmInterpLibDir = libdir
|
|
| 86 | + , wasmInterpOpts = interpOpts opts
|
|
| 87 | + , wasmInterpBrowser = interpBrowser opts
|
|
| 88 | + , wasmInterpBrowserHost = interpBrowserHost opts
|
|
| 89 | + , wasmInterpBrowserPort = interpBrowserPort opts
|
|
| 90 | + , wasmInterpBrowserRedirectWasiConsole = interpBrowserRedirectWasiConsole opts
|
|
| 91 | + , wasmInterpBrowserPuppeteerLaunchOpts = interpBrowserPuppeteerLaunchOpts opts
|
|
| 92 | + , wasmInterpBrowserPlaywrightBrowserType = interpBrowserPlaywrightBrowserType opts
|
|
| 93 | + , wasmInterpBrowserPlaywrightLaunchOpts = interpBrowserPlaywrightLaunchOpts opts
|
|
| 94 | + , wasmInterpTargetPlatform = platform
|
|
| 95 | + , wasmInterpProfiled = profiled
|
|
| 96 | + , wasmInterpHsSoSuffix = way_tag ++ dynLibSuffix (interpNameVer opts)
|
|
| 97 | + , wasmInterpUnitState = ue_homeUnitState unit_env
|
|
| 98 | + }
|
|
| 99 | + pure $ Just $ Interp (ExternalInterp $ ExtWasm $ ExtInterpState cfg s) loader lookup_cache
|
|
| 100 | +#endif
|
|
| 101 | + |
|
| 102 | + -- JavaScript interpreter
|
|
| 103 | + | ArchJavaScript <- platformArch platform
|
|
| 104 | + -> do
|
|
| 105 | + s <- liftIO $ newMVar InterpPending
|
|
| 106 | + loader <- liftIO Loader.uninitializedLoader
|
|
| 107 | + let cfg = JSInterpConfig
|
|
| 108 | + { jsInterpNodeConfig = defaultNodeJsSettings
|
|
| 109 | + , jsInterpScript = interpJsInterp opts
|
|
| 110 | + , jsInterpTmpFs = tmpfs
|
|
| 111 | + , jsInterpTmpDir = interpTmpDir opts
|
|
| 112 | + , jsInterpLogger = logger
|
|
| 113 | + , jsInterpCodegenCfg = interpJsCodegenCfg opts
|
|
| 114 | + , jsInterpUnitEnv = unit_env
|
|
| 115 | + , jsInterpFinderOpts = interpFinderOpts opts
|
|
| 116 | + , jsInterpFinderCache = finder_cache
|
|
| 117 | + }
|
|
| 118 | + return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader lookup_cache))
|
|
| 119 | + |
|
| 120 | + -- external interpreter
|
|
| 121 | + | interpExternal opts
|
|
| 122 | + -> do
|
|
| 123 | + let
|
|
| 124 | + profiled = interpWays opts `hasWay` WayProf
|
|
| 125 | + dynamic = interpWays opts `hasWay` WayDyn
|
|
| 126 | + prog <- case interpProg opts of
|
|
| 127 | + -- build iserv program if none specified
|
|
| 128 | + "" -> generateIservC logger tmpfs (interpExecutableLinkOpts opts) unit_env
|
|
| 129 | + _ -> pure (interpProg opts ++ flavour)
|
|
| 130 | + where
|
|
| 131 | + flavour
|
|
| 132 | + | profiled && dynamic = "-prof-dyn"
|
|
| 133 | + | profiled = "-prof"
|
|
| 134 | + | dynamic = "-dyn"
|
|
| 135 | + | otherwise = ""
|
|
| 136 | + let msg = text "Starting " <> text prog
|
|
| 137 | + tr <- if interpVerbosity opts >= 3
|
|
| 138 | + then return (logInfo logger $ withPprStyle defaultDumpStyle msg)
|
|
| 139 | + else return (pure ())
|
|
| 140 | + let
|
|
| 141 | + conf = IServConfig
|
|
| 142 | + { iservConfProgram = prog
|
|
| 143 | + , iservConfOpts = interpOpts opts
|
|
| 144 | + , iservConfProfiled = profiled
|
|
| 145 | + , iservConfDynamic = dynamic
|
|
| 146 | + , iservConfHook = interpCreateProcess opts
|
|
| 147 | + , iservConfTrace = tr
|
|
| 148 | + }
|
|
| 149 | + s <- liftIO $ newMVar InterpPending
|
|
| 150 | + loader <- liftIO Loader.uninitializedLoader
|
|
| 151 | + return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader lookup_cache))
|
|
| 152 | + |
|
| 153 | + -- Internal interpreter
|
|
| 154 | + | otherwise
|
|
| 155 | + ->
|
|
| 156 | +#if defined(HAVE_INTERNAL_INTERPRETER)
|
|
| 157 | + do
|
|
| 158 | + loader <- liftIO Loader.uninitializedLoader
|
|
| 159 | + return (Just (Interp InternalInterp loader lookup_cache))
|
|
| 160 | +#else
|
|
| 161 | + return Nothing
|
|
| 162 | +#endif |
| ... | ... | @@ -13,7 +13,11 @@ module GHC.SysTools.Tasks |
| 13 | 13 | , runSourceCodePreprocessor
|
| 14 | 14 | , runPp
|
| 15 | 15 | , runCc
|
| 16 | + , configureCc
|
|
| 17 | + , CcConfig (..)
|
|
| 18 | + , configureLd
|
|
| 16 | 19 | , askLd
|
| 20 | + , LdConfig(..)
|
|
| 17 | 21 | , runAs
|
| 18 | 22 | , runLlvmOpt
|
| 19 | 23 | , runLlvmLlc
|
| ... | ... | @@ -22,10 +26,20 @@ module GHC.SysTools.Tasks |
| 22 | 26 | , figureLlvmVersion
|
| 23 | 27 | , runMergeObjects
|
| 24 | 28 | , runAr
|
| 29 | + , ArConfig (..)
|
|
| 30 | + , configureAr
|
|
| 25 | 31 | , askOtool
|
| 32 | + , configureOtool
|
|
| 33 | + , OtoolConfig (..)
|
|
| 26 | 34 | , runInstallNameTool
|
| 35 | + , InstallNameConfig (..)
|
|
| 36 | + , configureInstallName
|
|
| 27 | 37 | , runRanlib
|
| 38 | + , RanlibConfig (..)
|
|
| 39 | + , configureRanlib
|
|
| 28 | 40 | , runWindres
|
| 41 | + , WindresConfig (..)
|
|
| 42 | + , configureWindres
|
|
| 29 | 43 | ) where
|
| 30 | 44 | |
| 31 | 45 | import GHC.Prelude
|
| ... | ... | @@ -207,15 +221,32 @@ runPp logger dflags args = traceSystoolCommand logger "pp" $ do |
| 207 | 221 | opts = map Option (getOpts dflags opt_F)
|
| 208 | 222 | runSomething logger "Haskell pre-processor" prog (args ++ opts)
|
| 209 | 223 | |
| 224 | +data CcConfig = CcConfig
|
|
| 225 | + { ccProg :: String
|
|
| 226 | + , cxxProg :: String
|
|
| 227 | + , ccOpts :: [String]
|
|
| 228 | + , cxxOpts :: [String]
|
|
| 229 | + , ccPicOpts :: [String]
|
|
| 230 | + }
|
|
| 231 | + |
|
| 232 | +configureCc :: DynFlags -> CcConfig
|
|
| 233 | +configureCc dflags = CcConfig
|
|
| 234 | + { ccProg = pgm_c dflags
|
|
| 235 | + , cxxProg = pgm_cxx dflags
|
|
| 236 | + , ccOpts = getOpts dflags opt_c
|
|
| 237 | + , cxxOpts = getOpts dflags opt_cxx
|
|
| 238 | + , ccPicOpts = picCCOpts dflags
|
|
| 239 | + }
|
|
| 240 | + |
|
| 210 | 241 | -- | Run compiler of C-like languages and raw objects (such as gcc or clang).
|
| 211 | -runCc :: Maybe ForeignSrcLang -> Logger -> TmpFs -> DynFlags -> [Option] -> IO ()
|
|
| 212 | -runCc mLanguage logger tmpfs dflags args = traceSystoolCommand logger "cc" $ do
|
|
| 242 | +runCc :: Maybe ForeignSrcLang -> Logger -> TmpFs -> TempDir -> CcConfig -> [Option] -> IO ()
|
|
| 243 | +runCc mLanguage logger tmpfs tmpdir opts args = traceSystoolCommand logger "cc" $ do
|
|
| 213 | 244 | let args1 = map Option userOpts
|
| 214 | 245 | args2 = languageOptions ++ args ++ args1
|
| 215 | 246 | -- We take care to pass -optc flags in args1 last to ensure that the
|
| 216 | 247 | -- user can override flags passed by GHC. See #14452.
|
| 217 | 248 | mb_env <- getGccEnv args2
|
| 218 | - runSomethingResponseFile logger tmpfs (tmpDir dflags) cc_filter dbgstring prog args2
|
|
| 249 | + runSomethingResponseFile logger tmpfs tmpdir cc_filter dbgstring prog args2
|
|
| 219 | 250 | mb_env
|
| 220 | 251 | where
|
| 221 | 252 | -- force the C compiler to interpret this file as C when
|
| ... | ... | @@ -223,38 +254,49 @@ runCc mLanguage logger tmpfs dflags args = traceSystoolCommand logger "cc" $ do |
| 223 | 254 | -- Also useful for plain .c files, just in case GHC saw a
|
| 224 | 255 | -- -x c option.
|
| 225 | 256 | (languageOptions, userOpts, prog, dbgstring) = case mLanguage of
|
| 226 | - Nothing -> ([], userOpts_c, pgm_c dflags, "C Compiler")
|
|
| 227 | - Just language -> ([Option "-x", Option languageName], opts, prog, dbgstr)
|
|
| 257 | + Nothing -> ([], ccOpts opts, ccProg opts, "C Compiler")
|
|
| 258 | + Just language -> ([Option "-x", Option languageName], copts, prog, dbgstr)
|
|
| 228 | 259 | where
|
| 229 | - (languageName, opts, prog, dbgstr) = case language of
|
|
| 230 | - LangC -> ("c", userOpts_c
|
|
| 231 | - ,pgm_c dflags, "C Compiler")
|
|
| 232 | - LangCxx -> ("c++", userOpts_cxx
|
|
| 233 | - ,pgm_cxx dflags , "C++ Compiler")
|
|
| 234 | - LangObjc -> ("objective-c", userOpts_c
|
|
| 235 | - ,pgm_c dflags , "Objective C Compiler")
|
|
| 236 | - LangObjcxx -> ("objective-c++", userOpts_cxx
|
|
| 237 | - ,pgm_cxx dflags, "Objective C++ Compiler")
|
|
| 260 | + (languageName, copts, prog, dbgstr) = case language of
|
|
| 261 | + LangC -> ("c", ccOpts opts
|
|
| 262 | + ,ccProg opts, "C Compiler")
|
|
| 263 | + LangCxx -> ("c++", cxxOpts opts
|
|
| 264 | + ,cxxProg opts, "C++ Compiler")
|
|
| 265 | + LangObjc -> ("objective-c", ccOpts opts
|
|
| 266 | + ,ccProg opts, "Objective C Compiler")
|
|
| 267 | + LangObjcxx -> ("objective-c++", cxxOpts opts
|
|
| 268 | + ,cxxProg opts, "Objective C++ Compiler")
|
|
| 238 | 269 | LangAsm -> ("assembler", []
|
| 239 | - ,pgm_c dflags, "Asm Compiler")
|
|
| 270 | + ,ccProg opts, "Asm Compiler")
|
|
| 240 | 271 | RawObject -> ("c", []
|
| 241 | - ,pgm_c dflags, "C Compiler") -- claim C for lack of a better idea
|
|
| 272 | + ,ccProg opts, "C Compiler") -- claim C for lack of a better idea
|
|
| 242 | 273 | --JS backend shouldn't reach here, so we just pass
|
| 243 | 274 | -- strings to satisfy the totality checker
|
| 244 | 275 | LangJs -> ("js", []
|
| 245 | - ,pgm_c dflags, "JS Backend Compiler")
|
|
| 246 | - userOpts_c = getOpts dflags opt_c
|
|
| 247 | - userOpts_cxx = getOpts dflags opt_cxx
|
|
| 276 | + ,ccProg opts, "JS Backend Compiler")
|
|
| 248 | 277 | |
| 249 | 278 | isContainedIn :: String -> String -> Bool
|
| 250 | 279 | xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
|
| 251 | 280 | |
| 252 | --- | Run the linker with some arguments and return the output
|
|
| 253 | -askLd :: Logger -> DynFlags -> [Option] -> IO String
|
|
| 254 | -askLd logger dflags args = traceSystoolCommand logger "linker" $ do
|
|
| 281 | +data LdConfig = LdConfig
|
|
| 282 | + { ldProg :: String -- ^ LD program path
|
|
| 283 | + , ldOpts :: [Option] -- ^ LD program arguments
|
|
| 284 | + }
|
|
| 285 | + |
|
| 286 | +configureLd :: DynFlags -> LdConfig
|
|
| 287 | +configureLd dflags =
|
|
| 255 | 288 | let (p,args0) = pgm_l dflags
|
| 256 | 289 | args1 = map Option (getOpts dflags opt_l)
|
| 257 | - args2 = args0 ++ args1 ++ args
|
|
| 290 | + in LdConfig
|
|
| 291 | + { ldProg = p
|
|
| 292 | + , ldOpts = args0 ++ args1
|
|
| 293 | + }
|
|
| 294 | + |
|
| 295 | +-- | Run the linker with some arguments and return the output
|
|
| 296 | +askLd :: Logger -> LdConfig -> [Option] -> IO String
|
|
| 297 | +askLd logger ld_config args = traceSystoolCommand logger "linker" $ do
|
|
| 298 | + let p = ldProg ld_config
|
|
| 299 | + args2 = ldOpts ld_config ++ args
|
|
| 258 | 300 | mb_env <- getGccEnv args2
|
| 259 | 301 | runSomethingWith logger "gcc" p args2 $ \real_args ->
|
| 260 | 302 | readCreateProcessWithExitCode' (proc p real_args){ env = mb_env }
|
| ... | ... | @@ -373,31 +415,80 @@ runMergeObjects logger tmpfs dflags args = |
| 373 | 415 | else do
|
| 374 | 416 | runSomething logger "Merge objects" p args2
|
| 375 | 417 | |
| 376 | -runAr :: Logger -> DynFlags -> Maybe FilePath -> [Option] -> IO ()
|
|
| 377 | -runAr logger dflags cwd args = traceSystoolCommand logger "ar" $ do
|
|
| 378 | - let ar = pgm_ar dflags
|
|
| 418 | +newtype ArConfig = ArConfig
|
|
| 419 | + { arProg :: String
|
|
| 420 | + }
|
|
| 421 | + |
|
| 422 | +configureAr :: DynFlags -> ArConfig
|
|
| 423 | +configureAr dflags = ArConfig
|
|
| 424 | + { arProg = pgm_ar dflags
|
|
| 425 | + }
|
|
| 426 | + |
|
| 427 | +runAr :: Logger -> ArConfig -> Maybe FilePath -> [Option] -> IO ()
|
|
| 428 | +runAr logger opts cwd args = traceSystoolCommand logger "ar" $ do
|
|
| 429 | + let ar = arProg opts
|
|
| 379 | 430 | runSomethingFiltered logger id "Ar" ar args cwd Nothing
|
| 380 | 431 | |
| 381 | -askOtool :: Logger -> ToolSettings -> Maybe FilePath -> [Option] -> IO String
|
|
| 382 | -askOtool logger toolSettings mb_cwd args = do
|
|
| 383 | - let otool = toolSettings_pgm_otool toolSettings
|
|
| 432 | +newtype OtoolConfig = OtoolConfig
|
|
| 433 | + { otoolProg :: String
|
|
| 434 | + }
|
|
| 435 | + |
|
| 436 | +configureOtool :: DynFlags -> OtoolConfig
|
|
| 437 | +configureOtool dflags = OtoolConfig
|
|
| 438 | + { otoolProg = toolSettings_pgm_otool (toolSettings dflags)
|
|
| 439 | + }
|
|
| 440 | + |
|
| 441 | +askOtool :: Logger -> OtoolConfig -> Maybe FilePath -> [Option] -> IO String
|
|
| 442 | +askOtool logger opts mb_cwd args = do
|
|
| 443 | + let otool = otoolProg opts
|
|
| 384 | 444 | runSomethingWith logger "otool" otool args $ \real_args ->
|
| 385 | 445 | readCreateProcessWithExitCode' (proc otool real_args){ cwd = mb_cwd }
|
| 386 | 446 | |
| 387 | -runInstallNameTool :: Logger -> ToolSettings -> [Option] -> IO ()
|
|
| 388 | -runInstallNameTool logger toolSettings args = do
|
|
| 389 | - let tool = toolSettings_pgm_install_name_tool toolSettings
|
|
| 447 | +newtype InstallNameConfig = InstallNameConfig
|
|
| 448 | + { installNameProg :: String
|
|
| 449 | + }
|
|
| 450 | + |
|
| 451 | +configureInstallName :: DynFlags -> InstallNameConfig
|
|
| 452 | +configureInstallName dflags = InstallNameConfig
|
|
| 453 | + { installNameProg = toolSettings_pgm_install_name_tool (toolSettings dflags)
|
|
| 454 | + }
|
|
| 455 | + |
|
| 456 | +runInstallNameTool :: Logger -> InstallNameConfig -> [Option] -> IO ()
|
|
| 457 | +runInstallNameTool logger opts args = do
|
|
| 458 | + let tool = installNameProg opts
|
|
| 390 | 459 | runSomethingFiltered logger id "Install Name Tool" tool args Nothing Nothing
|
| 391 | 460 | |
| 392 | -runRanlib :: Logger -> DynFlags -> [Option] -> IO ()
|
|
| 393 | -runRanlib logger dflags args = traceSystoolCommand logger "ranlib" $ do
|
|
| 394 | - let ranlib = pgm_ranlib dflags
|
|
| 461 | +newtype RanlibConfig = RanlibConfig
|
|
| 462 | + { ranlibProg :: String
|
|
| 463 | + }
|
|
| 464 | + |
|
| 465 | +configureRanlib :: DynFlags -> RanlibConfig
|
|
| 466 | +configureRanlib dflags = RanlibConfig
|
|
| 467 | + { ranlibProg = pgm_ranlib dflags
|
|
| 468 | + }
|
|
| 469 | + |
|
| 470 | +runRanlib :: Logger -> RanlibConfig -> [Option] -> IO ()
|
|
| 471 | +runRanlib logger opts args = traceSystoolCommand logger "ranlib" $ do
|
|
| 472 | + let ranlib = ranlibProg opts
|
|
| 395 | 473 | runSomethingFiltered logger id "Ranlib" ranlib args Nothing Nothing
|
| 396 | 474 | |
| 397 | -runWindres :: Logger -> DynFlags -> [Option] -> IO ()
|
|
| 398 | -runWindres logger dflags args = traceSystoolCommand logger "windres" $ do
|
|
| 399 | - let cc_args = map Option (sOpt_c (settings dflags))
|
|
| 400 | - windres = pgm_windres dflags
|
|
| 401 | - opts = map Option (getOpts dflags opt_windres)
|
|
| 475 | +data WindresConfig = WindresConfig
|
|
| 476 | + { windresProg :: String
|
|
| 477 | + , windresOpts :: [Option]
|
|
| 478 | + , windresCOpts :: [Option]
|
|
| 479 | + }
|
|
| 480 | + |
|
| 481 | +configureWindres :: DynFlags -> WindresConfig
|
|
| 482 | +configureWindres dflags = WindresConfig
|
|
| 483 | + { windresProg = pgm_windres dflags
|
|
| 484 | + , windresOpts = map Option (getOpts dflags opt_windres)
|
|
| 485 | + , windresCOpts = map Option (sOpt_c (settings dflags))
|
|
| 486 | + }
|
|
| 487 | + |
|
| 488 | +runWindres :: Logger -> WindresConfig -> [Option] -> IO ()
|
|
| 489 | +runWindres logger opts args = traceSystoolCommand logger "windres" $ do
|
|
| 490 | + let cc_args = windresCOpts opts
|
|
| 491 | + windres = windresProg opts
|
|
| 492 | + wopts = windresOpts opts
|
|
| 402 | 493 | mb_env <- getGccEnv cc_args
|
| 403 | - runSomethingFiltered logger id "Windres" windres (opts ++ args) Nothing mb_env |
|
| 494 | + runSomethingFiltered logger id "Windres" windres (wopts ++ args) Nothing mb_env |
| ... | ... | @@ -515,6 +515,7 @@ Library |
| 515 | 515 | GHC.Driver.Config.HsToCore
|
| 516 | 516 | GHC.Driver.Config.HsToCore.Ticks
|
| 517 | 517 | GHC.Driver.Config.HsToCore.Usage
|
| 518 | + GHC.Driver.Config.Interpreter
|
|
| 518 | 519 | GHC.Driver.Config.Linker
|
| 519 | 520 | GHC.Driver.Config.Logger
|
| 520 | 521 | GHC.Driver.Config.Parser
|
| ... | ... | @@ -650,7 +651,7 @@ Library |
| 650 | 651 | GHC.Linker.Deps
|
| 651 | 652 | GHC.Linker.Dynamic
|
| 652 | 653 | GHC.Linker.External
|
| 653 | - GHC.Linker.ExtraObj
|
|
| 654 | + GHC.Linker.Executable
|
|
| 654 | 655 | GHC.Linker.Loader
|
| 655 | 656 | GHC.Linker.MacOS
|
| 656 | 657 | GHC.Linker.Static
|
| ... | ... | @@ -723,6 +724,8 @@ Library |
| 723 | 724 | GHC.Runtime.Heap.Inspect
|
| 724 | 725 | GHC.Runtime.Heap.Layout
|
| 725 | 726 | GHC.Runtime.Interpreter
|
| 727 | + GHC.Runtime.Interpreter.C
|
|
| 728 | + GHC.Runtime.Interpreter.Init
|
|
| 726 | 729 | GHC.Runtime.Interpreter.JS
|
| 727 | 730 | GHC.Runtime.Interpreter.Process
|
| 728 | 731 | GHC.Runtime.Interpreter.Types
|
| 1 | +{-# LANGUAGE GADTs #-}
|
|
| 2 | +{-# LANGUAGE LinearTypes #-}
|
|
| 3 | + |
|
| 4 | +module Main (main) where
|
|
| 5 | + |
|
| 6 | +data Ur a where
|
|
| 7 | + Ur :: a -> Ur a
|
|
| 8 | + |
|
| 9 | +unur :: Ur a -> a
|
|
| 10 | +unur (Ur a) = a
|
|
| 11 | + |
|
| 12 | +segvGHCi :: Ur ()
|
|
| 13 | +segvGHCi = Ur $ ()
|
|
| 14 | + |
|
| 15 | +main :: IO ()
|
|
| 16 | +main = print (unur segvGHCi)
|
|
| 17 | + |
| 1 | +:l T23973.hs
|
|
| 2 | +main |
| 1 | +() |
| 1 | +{-# LANGUAGE LinearTypes #-}
|
|
| 2 | +module Test where
|
|
| 3 | + |
|
| 4 | +data Ur a where
|
|
| 5 | + Ur :: a -> Ur a
|
|
| 6 | + |
| 1 | +:l T26565
|
|
| 2 | +Ur y = (\x -> Ur $ replicate 5 'a') 3
|
|
| 3 | +y |
| 1 | +"aaaaa" |
| ... | ... | @@ -6,6 +6,8 @@ test('T25975', extra_ways(ghci_ways), compile_and_run, |
| 6 | 6 | # Some of the examples work more robustly with these flags
|
| 7 | 7 | ['-fno-break-points -fno-full-laziness'])
|
| 8 | 8 | |
| 9 | +test('T26565', extra_files(["T26565.hs"]), ghci_script, ['T26565.script'])
|
|
| 10 | +test('T23973', extra_files(["T23973.hs"]), ghci_script, ['T23973.script'])
|
|
| 11 | + |
|
| 9 | 12 | # Nullary data constructors
|
| 10 | 13 | test('T26216', extra_files(["T26216_aux.hs"]), ghci_script, ['T26216.script']) |
| 11 | - |
| 1 | +{-# LANGUAGE TemplateHaskell #-}
|
|
| 2 | +module T24731 where
|
|
| 3 | + |
|
| 4 | +foo :: Int
|
|
| 5 | +foo = $([|10|]) |
| ... | ... | @@ -333,3 +333,4 @@ test('T25382', normal, makefile_test, []) |
| 333 | 333 | test('T26018', req_c, makefile_test, [])
|
| 334 | 334 | test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib'])
|
| 335 | 335 | test('T26551', [extra_files(['T26551.hs'])], makefile_test, [])
|
| 336 | +test('T24731', [only_ways(['ext-interp'])], compile, ['-fexternal-interpreter -pgmi ""']) |
| ... | ... | @@ -30,15 +30,6 @@ Executable iserv |
| 30 | 30 | C-Sources: cbits/iservmain.c
|
| 31 | 31 | Hs-Source-Dirs: src
|
| 32 | 32 | include-dirs: .
|
| 33 | - Build-Depends: array >= 0.5 && < 0.6,
|
|
| 34 | - base >= 4 && < 5,
|
|
| 35 | - binary >= 0.7 && < 0.11,
|
|
| 36 | - bytestring >= 0.10 && < 0.13,
|
|
| 37 | - containers >= 0.5 && < 0.9,
|
|
| 38 | - deepseq >= 1.4 && < 1.6,
|
|
| 39 | - ghci == @ProjectVersionMunged@
|
|
| 40 | - |
|
| 41 | - if os(windows)
|
|
| 42 | - Cpp-Options: -DWINDOWS
|
|
| 43 | - else
|
|
| 44 | - Build-Depends: unix >= 2.7 && < 2.9 |
|
| 33 | + Build-Depends:
|
|
| 34 | + base >= 4 && < 5,
|
|
| 35 | + ghci == @ProjectVersionMunged@ |