Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

17 changed files:

Changes:

  • driver/utils/merge_sections.ld deleted
    1
    -/* Linker script to undo -split-sections and merge all sections together when
    
    2
    - * linking relocatable object files for GHCi.
    
    3
    - * ld -r normally retains the individual sections, which is what you would want
    
    4
    - * if the intention is to eventually link into a binary with --gc-sections, but
    
    5
    - * it doesn't have a flag for directly doing what we want. */
    
    6
    -SECTIONS
    
    7
    -{
    
    8
    -    .text : {
    
    9
    -        *(.text*)
    
    10
    -    }
    
    11
    -    .rodata.cst16 : {
    
    12
    -        *(.rodata.cst16*)
    
    13
    -    }
    
    14
    -    .rodata : {
    
    15
    -        *(.rodata*)
    
    16
    -    }
    
    17
    -    .data.rel.ro : {
    
    18
    -        *(.data.rel.ro*)
    
    19
    -    }
    
    20
    -    .data : {
    
    21
    -        *(.data*)
    
    22
    -    }
    
    23
    -    .bss : {
    
    24
    -        *(.bss*)
    
    25
    -    }
    
    26
    -}

  • driver/utils/merge_sections_pe.ld deleted
    1
    -/* Linker script to undo -split-sections and merge all sections together when
    
    2
    - * linking relocatable object files for GHCi.
    
    3
    - * ld -r normally retains the individual sections, which is what you would want
    
    4
    - * if the intention is to eventually link into a binary with --gc-sections, but
    
    5
    - * it doesn't have a flag for directly doing what we want. */
    
    6
    -SECTIONS
    
    7
    -{
    
    8
    -    .text : {
    
    9
    -        *(.text$*)
    
    10
    -    }
    
    11
    -    .rdata : {
    
    12
    -        *(.rdata$*)
    
    13
    -    }
    
    14
    -    .data : {
    
    15
    -        *(.data$*)
    
    16
    -    }
    
    17
    -    .pdata : {
    
    18
    -        *(.pdata$*)
    
    19
    -    }
    
    20
    -    .xdata : {
    
    21
    -        *(.xdata$*)
    
    22
    -    }
    
    23
    -    .bss : {
    
    24
    -        *(.bss$*)
    
    25
    -    }
    
    26
    -}

  • hadrian/hadrian.cabal
    ... ... @@ -115,7 +115,6 @@ executable hadrian
    115 115
                            , Settings.Builders.Ar
    
    116 116
                            , Settings.Builders.Ld
    
    117 117
                            , Settings.Builders.Make
    
    118
    -                       , Settings.Builders.MergeObjects
    
    119 118
                            , Settings.Builders.SplitSections
    
    120 119
                            , Settings.Builders.RunTest
    
    121 120
                            , Settings.Builders.Win32Tarballs
    

  • hadrian/src/Builder.hs
    ... ... @@ -178,7 +178,6 @@ data Builder = Alex
    178 178
                  | Ld Stage --- ^ linker
    
    179 179
                  | Make FilePath
    
    180 180
                  | Makeinfo
    
    181
    -             | MergeObjects Stage -- ^ linker to be used to merge object files.
    
    182 181
                  | Nm
    
    183 182
                  | Objdump
    
    184 183
                  | Python
    
    ... ... @@ -453,15 +452,6 @@ systemBuilderPath builder = case builder of
    453 452
         HsCpp           -> fromTargetTC "hs-cpp" (Toolchain.hsCppProgram . tgtHsCPreprocessor)
    
    454 453
         JsCpp           -> fromTargetTC "js-cpp" (maybeProg Toolchain.jsCppProgram . tgtJsCPreprocessor)
    
    455 454
         Ld _            -> fromTargetTC "ld" (Toolchain.ccLinkProgram . tgtCCompilerLink)
    
    456
    -    -- MergeObjects Stage0 is a special case in case of
    
    457
    -    -- cross-compiling. We're building stage1, e.g. code which will be
    
    458
    -    -- executed on the host and hence we need to use host's merge
    
    459
    -    -- objects tool and not the target merge object tool.
    
    460
    -    -- Note, merge object tool is usually platform linker with some
    
    461
    -    -- parameters. E.g. building a cross-compiler on and for x86_64
    
    462
    -    -- which will target ppc64 means that MergeObjects Stage0 will use
    
    463
    -    -- x86_64 linker and MergeObject _ will use ppc64 linker.
    
    464
    -    MergeObjects st -> fromStageTC st "merge-objects" (maybeProg Toolchain.mergeObjsProgram . tgtMergeObjs)
    
    465 455
         Make _          -> fromKey "make"
    
    466 456
         Makeinfo        -> fromKey "makeinfo"
    
    467 457
         Nm              -> fromTargetTC "nm" (Toolchain.nmProgram . tgtNm)
    

  • hadrian/src/Context.hs
    ... ... @@ -8,7 +8,7 @@ module Context (
    8 8
         -- * Paths
    
    9 9
         contextDir, buildPath, buildDir, pkgInplaceConfig, pkgSetupConfigFile, pkgSetupConfigDir,
    
    10 10
         pkgHaddockFile, pkgRegisteredLibraryFile, pkgRegisteredLibraryFileName,
    
    11
    -    pkgLibraryFile, pkgGhciLibraryFile,
    
    11
    +    pkgLibraryFile,
    
    12 12
         pkgConfFile, pkgStampFile, resourcePath, objectPath, contextPath, getContextPath, libPath, distDir,
    
    13 13
         distDynDir,
    
    14 14
         haddockStatsFilesDir, ensureConfigured, autogenPath, rtsContext, rtsBuildPath, libffiBuildPath
    
    ... ... @@ -155,13 +155,6 @@ pkgLibraryFile context@Context {..} = do
    155 155
         extension <- libsuf stage way
    
    156 156
         pkgFile context "libHS" extension
    
    157 157
     
    
    158
    --- | Path to the GHCi library file of a given 'Context', e.g.:
    
    159
    --- @_build/stage1/libraries/array/build/HSarray-0.5.1.0.o@.
    
    160
    -pkgGhciLibraryFile :: Context -> Action FilePath
    
    161
    -pkgGhciLibraryFile context@Context {..} = do
    
    162
    -    let extension = "" <.> osuf way
    
    163
    -    pkgFile context "HS" extension
    
    164
    -
    
    165 158
     -- | Path to the configuration file of a given 'Context'.
    
    166 159
     pkgConfFile :: Context -> Action FilePath
    
    167 160
     pkgConfFile Context {..} = do
    

  • hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
    ... ... @@ -334,7 +334,6 @@ resolveContextData context@Context {..} = do
    334 334
               , depIncludeDirs     = forDeps Installed.includeDirs
    
    335 335
               , depCcOpts          = forDeps Installed.ccOptions
    
    336 336
               , depLdOpts          = forDeps Installed.ldOptions
    
    337
    -          , buildGhciLib       = C.withGHCiLib lbi'
    
    338 337
               , frameworks         = map C.getSymbolicPath (C.frameworks buildInfo)
    
    339 338
               , packageDescription = pd'
    
    340 339
               , contextLibdir        = libdir install_dirs
    

  • hadrian/src/Hadrian/Haskell/Cabal/Type.hs
    ... ... @@ -67,7 +67,6 @@ data ContextData = ContextData
    67 67
         , depIncludeDirs     :: [String]
    
    68 68
         , depCcOpts          :: [String]
    
    69 69
         , depLdOpts          :: [String]
    
    70
    -    , buildGhciLib       :: Bool
    
    71 70
         , frameworks         :: [String]
    
    72 71
         , packageDescription :: PackageDescription
    
    73 72
     
    

  • hadrian/src/Hadrian/Haskell/Hash.hs
    ... ... @@ -82,7 +82,6 @@ data PackageHashConfigInputs = PackageHashConfigInputs {
    82 82
            pkgHashVanillaLib          :: Bool,
    
    83 83
            pkgHashSharedLib           :: Bool,
    
    84 84
            pkgHashDynExe              :: Bool,
    
    85
    -       pkgHashGHCiLib             :: Bool,
    
    86 85
            pkgHashProfLib             :: Bool,
    
    87 86
            pkgHashProfExe             :: Bool,
    
    88 87
            pkgHashSplitObjs           :: Bool,
    
    ... ... @@ -139,7 +138,6 @@ pkgHashOracle = void $ addOracleCache $ \(PkgHashKey (stag, pkg)) -> do
    139 138
           pkgHashVanillaLib = vanilla `Set.member` libWays
    
    140 139
           pkgHashSharedLib = dynamic `Set.member` libWays
    
    141 140
           pkgHashDynExe = dyn_ghc
    
    142
    -      pkgHashGHCiLib = False
    
    143 141
           pkgHashProfLib = profiling `Set.member` libWays
    
    144 142
           pkgHashProfExe = pkg == ghc && ghcProfiled flav stag
    
    145 143
           pkgHashSplitObjs = False -- Deprecated
    
    ... ... @@ -239,7 +237,6 @@ renderPackageHashInputs PackageHashInputs{
    239 237
           , opt   "vanilla-lib" True  show pkgHashVanillaLib
    
    240 238
           , opt   "shared-lib"  False show pkgHashSharedLib
    
    241 239
           , opt   "dynamic-exe" False show pkgHashDynExe
    
    242
    -      , opt   "ghci-lib"    False show pkgHashGHCiLib
    
    243 240
           , opt   "prof-lib"    False show pkgHashProfLib
    
    244 241
           , opt   "prof-exe"    False show pkgHashProfExe
    
    245 242
           , opt   "split-objs"   False show pkgHashSplitObjs
    

  • hadrian/src/Oracles/Flag.hs
    ... ... @@ -3,7 +3,6 @@
    3 3
     module Oracles.Flag (
    
    4 4
         Flag (..), flag, getFlag,
    
    5 5
         platformSupportsSharedLibs,
    
    6
    -    platformSupportsGhciObjects,
    
    7 6
         targetRTSLinkerOnlySupportsSharedLibs,
    
    8 7
         targetSupportsThreadedRts,
    
    9 8
         targetSupportsSMP,
    
    ... ... @@ -71,15 +70,6 @@ flag f = do
    71 70
     getFlag :: Flag -> Expr c b Bool
    
    72 71
     getFlag = expr . flag
    
    73 72
     
    
    74
    --- | Does the platform support object merging (and therefore we can build GHCi objects
    
    75
    --- when appropriate).
    
    76
    -platformSupportsGhciObjects :: Action Bool
    
    77
    --- FIXME: The name of the function is not entirely clear about which platform, it would be better named targetSupportsGhciObjects
    
    78
    -platformSupportsGhciObjects = do
    
    79
    -    has_merge_objs <- isJust <$> queryTargetTarget tgtMergeObjs
    
    80
    -    only_shared_libs <- targetRTSLinkerOnlySupportsSharedLibs
    
    81
    -    pure $ has_merge_objs && not only_shared_libs
    
    82
    -
    
    83 73
     targetRTSLinkerOnlySupportsSharedLibs :: Action Bool
    
    84 74
     targetRTSLinkerOnlySupportsSharedLibs = queryTargetTarget Toolchain.tgtRTSLinkerOnlySupportsSharedLibs
    
    85 75
     
    

  • hadrian/src/Rules.hs
    ... ... @@ -71,16 +71,9 @@ topLevelTargets = action $ do
    71 71
         name stage pkg | isLibrary pkg = return (pkgName pkg)
    
    72 72
                        | otherwise     = programName (vanillaContext stage pkg)
    
    73 73
     
    
    74
    --- TODO: Get rid of the @includeGhciLib@ hack.
    
    75 74
     -- | Return the list of targets associated with a given 'Stage' and 'Package'.
    
    76
    --- By setting the Boolean parameter to False it is possible to exclude the GHCi
    
    77
    --- library from the targets, and avoid configuring the package to determine
    
    78
    --- whether GHCi library needs to be built for it. We typically want to set
    
    79
    --- this parameter to True, however it is important to set it to False when
    
    80
    --- computing 'topLevelTargets', as otherwise the whole build gets sequentialised
    
    81
    --- because packages are configured in the order respecting their dependencies.
    
    82
    -packageTargets :: Bool -> Stage -> Package -> Action [FilePath]
    
    83
    -packageTargets includeGhciLib stage pkg = do
    
    75
    +packageTargets :: Stage -> Package -> Action [FilePath]
    
    76
    +packageTargets stage pkg = do
    
    84 77
         let context = vanillaContext stage pkg
    
    85 78
         activePackages <- stagePackages stage
    
    86 79
         if pkg `notElem` activePackages
    
    ... ... @@ -90,7 +83,7 @@ packageTargets includeGhciLib stage pkg = do
    90 83
                 let pkgWays = if pkg == rts then getRtsWays else getLibraryWays
    
    91 84
                 ways  <- interpretInContext context pkgWays
    
    92 85
                 libs  <- mapM (\w -> pkgLibraryFile (Context stage pkg w (error "unused"))) (Set.toList ways)
    
    93
    -            more  <- Rules.Library.libraryTargets includeGhciLib context
    
    86
    +            more  <- Rules.Library.libraryTargets context
    
    94 87
                 setupConfig <- pkgSetupConfigFile context
    
    95 88
                 return $ [setupConfig] ++ libs ++ more
    
    96 89
             else do -- The only target of a program package is the executable.
    

  • hadrian/src/Rules/Library.hs
    ... ... @@ -35,8 +35,6 @@ libraryRules = do
    35 35
             root -/- "stage*/lib/**/libHS*-*.so"    %> registerDynamicLib root "so"
    
    36 36
             root -/- "stage*/lib/**/libHS*-*.dll"   %> registerDynamicLib root "dll"
    
    37 37
             root -/- "stage*/lib/**/*.a"            %> registerStaticLib  root
    
    38
    -        root -/- "**/HS*-*.o"   %> buildGhciLibO root
    
    39
    -        root -/- "**/HS*-*.p_o" %> buildGhciLibO root
    
    40 38
     
    
    41 39
     -- * 'Action's for building libraries
    
    42 40
     
    
    ... ... @@ -100,20 +98,6 @@ buildDynamicLib root suffix dynlibpath = do
    100 98
             (quote pkgname ++ " (" ++ show stage ++ ", way " ++ show way ++ ").")
    
    101 99
             dynlibpath synopsis
    
    102 100
     
    
    103
    --- | Build a "GHCi library" ('LibGhci') under the given build root, with the
    
    104
    --- complete path of the file to build is given as the second argument.
    
    105
    --- See Note [Merging object files for GHCi] in GHC.Driver.Pipeline.
    
    106
    -buildGhciLibO :: FilePath -> FilePath -> Action ()
    
    107
    -buildGhciLibO root ghcilibPath = do
    
    108
    -    l@(BuildPath _ stage _ (LibGhci _ _ _ _))
    
    109
    -        <- parsePath (parseBuildLibGhci root)
    
    110
    -                     "<.o ghci lib (build) path parser>"
    
    111
    -                     ghcilibPath
    
    112
    -    let context = libGhciContext l
    
    113
    -    objs <- allObjects context
    
    114
    -    need objs
    
    115
    -    build $ target context (MergeObjects stage) objs [ghcilibPath]
    
    116
    -
    
    117 101
     
    
    118 102
     {-
    
    119 103
     Note [Stamp Files]
    
    ... ... @@ -145,7 +129,7 @@ buildPackage root fp = do
    145 129
       srcs <- hsSources ctx
    
    146 130
       gens <- interpretInContext ctx generatedDependencies
    
    147 131
     
    
    148
    -  lib_targets <- libraryTargets True ctx
    
    132
    +  lib_targets <- libraryTargets ctx
    
    149 133
     
    
    150 134
       need (srcs ++ gens ++ lib_targets)
    
    151 135
     
    
    ... ... @@ -166,10 +150,6 @@ buildPackage root fp = do
    166 150
     
    
    167 151
     -- * Helpers
    
    168 152
     
    
    169
    --- | Return all Haskell and non-Haskell object files for the given 'Context'.
    
    170
    -allObjects :: Context -> Action [FilePath]
    
    171
    -allObjects context = (++) <$> nonHsObjects context <*> hsObjects context
    
    172
    -
    
    173 153
     -- | Return all the non-Haskell object files for the given library context
    
    174 154
     -- (object files built from C, C-- and sometimes other things).
    
    175 155
     nonHsObjects :: Context -> Action [FilePath]
    
    ... ... @@ -228,7 +208,7 @@ libraryObjects context = do
    228 208
     
    
    229 209
     -- | Coarse-grain 'need': make sure all given libraries are fully built.
    
    230 210
     needLibrary :: [Context] -> Action ()
    
    231
    -needLibrary cs = need =<< concatMapM (libraryTargets True) cs
    
    211
    +needLibrary cs = need =<< concatMapM libraryTargets cs
    
    232 212
     
    
    233 213
     -- * Library paths types and parsers
    
    234 214
     
    
    ... ... @@ -241,9 +221,6 @@ data DynLibExt = So | Dylib deriving (Eq, Show)
    241 221
     -- | > libHS<pkg name>-<pkg version>-<pkg hash>[_<way suffix>]-ghc<ghc version>.<so|dylib>
    
    242 222
     data LibDyn = LibDyn String [Integer] String Way DynLibExt deriving (Eq, Show)
    
    243 223
     
    
    244
    --- | > HS<pkg name>-<pkg version>-<pkg hash>[_<way suffix>].o
    
    245
    -data LibGhci = LibGhci String [Integer] String Way deriving (Eq, Show)
    
    246
    -
    
    247 224
     -- | Get the 'Context' corresponding to the build path for a given static library.
    
    248 225
     libAContext :: BuildPath LibA -> Context
    
    249 226
     libAContext (BuildPath _ stage pkgpath (LibA pkgname _ _ way)) =
    
    ... ... @@ -251,13 +228,6 @@ libAContext (BuildPath _ stage pkgpath (LibA pkgname _ _ way)) =
    251 228
       where
    
    252 229
         pkg = library pkgname pkgpath
    
    253 230
     
    
    254
    --- | Get the 'Context' corresponding to the build path for a given GHCi library.
    
    255
    -libGhciContext :: BuildPath LibGhci -> Context
    
    256
    -libGhciContext (BuildPath _ stage pkgpath (LibGhci pkgname _ _ way)) =
    
    257
    -    Context stage pkg way Final
    
    258
    -  where
    
    259
    -    pkg = library pkgname pkgpath
    
    260
    -
    
    261 231
     -- | Get the 'Context' corresponding to the build path for a given dynamic library.
    
    262 232
     libDynContext :: BuildPath LibDyn -> Context
    
    263 233
     libDynContext (BuildPath _ stage pkgpath (LibDyn pkgname _ _ way _)) =
    
    ... ... @@ -274,9 +244,8 @@ stampContext (BuildPath _ stage _ (PkgStamp pkgname _ _ way)) =
    274 244
     
    
    275 245
     data PkgStamp = PkgStamp String [Integer] String Way deriving (Eq, Show)
    
    276 246
     
    
    277
    -
    
    278
    --- | Parse a path to a ghci library to be built, making sure the path starts
    
    279
    --- with the given build root.
    
    247
    +-- | Parse a path to a package stamp file, making sure the path starts with the
    
    248
    +-- given build root.
    
    280 249
     parseStampPath :: FilePath -> Parsec.Parsec String () (BuildPath PkgStamp)
    
    281 250
     parseStampPath root = parseBuildPath root parseStamp
    
    282 251
     
    
    ... ... @@ -297,12 +266,6 @@ parseBuildLibA :: FilePath -> Parsec.Parsec String () (BuildPath LibA)
    297 266
     parseBuildLibA root = parseBuildPath root parseLibAFilename
    
    298 267
         Parsec.<?> "build path for a static library"
    
    299 268
     
    
    300
    --- | Parse a path to a ghci library to be built, making sure the path starts
    
    301
    --- with the given build root.
    
    302
    -parseBuildLibGhci :: FilePath -> Parsec.Parsec String () (BuildPath LibGhci)
    
    303
    -parseBuildLibGhci root = parseBuildPath root parseLibGhciFilename
    
    304
    -    Parsec.<?> "build path for a ghci library"
    
    305
    -
    
    306 269
     -- | Parse a path to a dynamic library to be built, making sure the path starts
    
    307 270
     -- with the given build root.
    
    308 271
     parseBuildLibDyn :: FilePath -> String -> Parsec.Parsec String () (BuildPath LibDyn)
    
    ... ... @@ -324,16 +287,6 @@ parseLibAFilename = do
    324 287
         _ <- Parsec.string ".a"
    
    325 288
         return (LibA pkgname pkgver pkghash way)
    
    326 289
     
    
    327
    --- | Parse the filename of a ghci library to be built into a 'LibGhci' value.
    
    328
    -parseLibGhciFilename :: Parsec.Parsec String () LibGhci
    
    329
    -parseLibGhciFilename = do
    
    330
    -    _ <- Parsec.string "HS"
    
    331
    -    (pkgname, pkgver, pkghash) <- parsePkgId
    
    332
    -    _ <- Parsec.string "."
    
    333
    -    way <- parseWayPrefix vanilla
    
    334
    -    _ <- Parsec.string "o"
    
    335
    -    return (LibGhci pkgname pkgver pkghash way)
    
    336
    -
    
    337 290
     -- | Parse the filename of a dynamic library to be built into a 'LibDyn' value.
    
    338 291
     parseLibDynFilename :: String -> Parsec.Parsec String () LibDyn
    
    339 292
     parseLibDynFilename ext = do
    

  • hadrian/src/Rules/Register.hs
    ... ... @@ -6,20 +6,17 @@ module Rules.Register (
    6 6
     
    
    7 7
     import Base
    
    8 8
     import Context
    
    9
    -import Expression ( getContextData )
    
    10 9
     import Flavour
    
    11 10
     import Oracles.Setting
    
    12 11
     import Hadrian.BuildPath
    
    13 12
     import Hadrian.Expression
    
    14 13
     import Hadrian.Haskell.Cabal
    
    15
    -import Oracles.Flag (platformSupportsGhciObjects)
    
    16 14
     import Packages
    
    17 15
     import Rules.Rts
    
    18 16
     import Settings
    
    19 17
     import Target
    
    20 18
     import Utilities
    
    21 19
     
    
    22
    -import Hadrian.Haskell.Cabal.Type
    
    23 20
     import qualified Text.Parsec      as Parsec
    
    24 21
     import qualified Data.Set         as Set
    
    25 22
     import qualified Data.Char        as Char
    
    ... ... @@ -298,17 +295,9 @@ extraTargets context
    298 295
     -- | Given a library 'Package' this action computes all of its targets. Needing
    
    299 296
     -- all the targets should build the library such that it is ready to be
    
    300 297
     -- registered into the package database.
    
    301
    --- See 'Rules.packageTargets' for the explanation of the @includeGhciLib@
    
    302
    --- parameter.
    
    303
    -libraryTargets :: Bool -> Context -> Action [FilePath]
    
    304
    -libraryTargets includeGhciLib context@Context {..} = do
    
    298
    +libraryTargets :: Context -> Action [FilePath]
    
    299
    +libraryTargets context = do
    
    305 300
         libFile  <- pkgLibraryFile     context
    
    306
    -    ghciLib  <- pkgGhciLibraryFile context
    
    307
    -    ghciObjsSupported <- platformSupportsGhciObjects
    
    308
    -    ghci     <- if ghciObjsSupported && includeGhciLib && not (wayUnit Dynamic way)
    
    309
    -                then interpretInContext context $ getContextData buildGhciLib
    
    310
    -                else return False
    
    311 301
         extra    <- extraTargets context
    
    312 302
         return $ [ libFile ]
    
    313
    -          ++ [ ghciLib | ghci ]
    
    314 303
               ++ extra

  • hadrian/src/Settings/Builders/Cabal.hs
    ... ... @@ -5,13 +5,12 @@ import Hadrian.Haskell.Cabal
    5 5
     
    
    6 6
     import Builder
    
    7 7
     import Context
    
    8
    -import Flavour
    
    9 8
     import Packages
    
    10 9
     import Settings.Builders.Common
    
    11 10
     import qualified Settings.Builders.Common as S
    
    12 11
     import Control.Exception (assert)
    
    13 12
     import qualified Data.Set as Set
    
    14
    -import Settings.Program (programContext, ghcWithInterpreter)
    
    13
    +import Settings.Program (programContext)
    
    15 14
     import GHC.Toolchain (ccLinkProgram, tgtCCompilerLink)
    
    16 15
     import GHC.Toolchain.Program (prgFlags)
    
    17 16
     
    
    ... ... @@ -128,7 +127,6 @@ commonCabalArgs stage = do
    128 127
                 ]
    
    129 128
     
    
    130 129
     -- TODO: Isn't vanilla always built? If yes, some conditions are redundant.
    
    131
    --- TODO: Need compiler_stage1_CONFIGURE_OPTS += --disable-library-for-ghci?
    
    132 130
     -- TODO: should `elem` be `wayUnit`?
    
    133 131
     -- This approach still doesn't work. Previously libraries were build only in the
    
    134 132
     -- Default flavours and not using context.
    
    ... ... @@ -136,11 +134,6 @@ libraryArgs :: Args
    136 134
     libraryArgs = do
    
    137 135
         flavourWays <- getLibraryWays
    
    138 136
         contextWay  <- getWay
    
    139
    -    package     <- getPackage
    
    140
    -    stage       <- getStage
    
    141
    -    withGhci    <- expr $ ghcWithInterpreter stage
    
    142
    -    dynPrograms <- expr (flavour >>= dynamicGhcPrograms)
    
    143
    -    ghciObjsSupported <- expr platformSupportsGhciObjects
    
    144 137
         let ways = Set.insert contextWay flavourWays
    
    145 138
             hasVanilla = vanilla `elem` ways
    
    146 139
             hasProfiling = any (wayUnit Profiling) ways
    
    ... ... @@ -155,11 +148,7 @@ libraryArgs = do
    155 148
              , if hasProfilingShared
    
    156 149
                 then "--enable-profiling-shared"
    
    157 150
                 else "--disable-profiling-shared"
    
    158
    -         , if ghciObjsSupported &&
    
    159
    -              (hasVanilla || hasProfiling) &&
    
    160
    -              package /= rts && withGhci && not dynPrograms
    
    161
    -           then  "--enable-library-for-ghci"
    
    162
    -           else "--disable-library-for-ghci"
    
    151
    +         , "--disable-library-for-ghci"
    
    163 152
              , if hasDynamic
    
    164 153
                then  "--enable-shared"
    
    165 154
                else "--disable-shared" ]
    

  • hadrian/src/Settings/Builders/MergeObjects.hs deleted
    1
    -module Settings.Builders.MergeObjects (mergeObjectsBuilderArgs) where
    
    2
    -
    
    3
    -import Settings.Builders.Common
    
    4
    -import GHC.Toolchain
    
    5
    -import GHC.Toolchain.Program
    
    6
    -
    
    7
    -mergeObjectsBuilderArgs :: Args
    
    8
    -mergeObjectsBuilderArgs = builder MergeObjects ? mconcat
    
    9
    -    [ maybe [] (prgFlags . mergeObjsProgram) . tgtMergeObjs <$> getStagedTarget
    
    10
    -    , arg "-o", arg =<< getOutput
    
    11
    -    , getInputs ]

  • hadrian/src/Settings/Builders/SplitSections.hs
    ... ... @@ -32,8 +32,5 @@ splitSectionsArgs = do
    32 32
             , builder (Ghc CompileCWithGhc) ? arg "-fsplit-sections"
    
    33 33
             , builder (Ghc CompileCppWithGhc) ? arg "-fsplit-sections"
    
    34 34
             , builder (Cc CompileC) ? arg "-ffunction-sections" <> arg "-fdata-sections"
    
    35
    -        , builder MergeObjects ? ifM (expr isWinTarget)
    
    36
    -            (pure ["-T", "driver/utils/merge_sections_pe.ld"])
    
    37
    -            (pure ["-T", "driver/utils/merge_sections.ld"])
    
    38 35
             ]
    
    39 36
         ) else mempty

  • hadrian/src/Settings/Default.hs
    ... ... @@ -40,7 +40,6 @@ import Settings.Builders.HsCpp
    40 40
     import Settings.Builders.Ar
    
    41 41
     import Settings.Builders.Ld
    
    42 42
     import Settings.Builders.Make
    
    43
    -import Settings.Builders.MergeObjects
    
    44 43
     import Settings.Builders.SplitSections
    
    45 44
     import Settings.Builders.RunTest
    
    46 45
     import Settings.Builders.Xelatex
    
    ... ... @@ -328,7 +327,6 @@ defaultBuilderArgs = mconcat
    328 327
         , ldBuilderArgs
    
    329 328
         , arBuilderArgs
    
    330 329
         , makeBuilderArgs
    
    331
    -    , mergeObjectsBuilderArgs
    
    332 330
         , runTestBuilderArgs
    
    333 331
         , validateBuilderArgs
    
    334 332
         , xelatexBuilderArgs
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -75,8 +75,7 @@ packageArgs = do
    75 75
                   pure ["-O0"] ]
    
    76 76
     
    
    77 77
               , builder (Cabal Setup) ? mconcat
    
    78
    -            [ arg "--disable-library-for-ghci"
    
    79
    -            , anyTargetOs [OSOpenBSD] ? arg "--ld-options=-E"
    
    78
    +            [ anyTargetOs [OSOpenBSD] ? arg "--ld-options=-E"
    
    80 79
                 , compilerStageOption ghcProfiled ? arg "--ghc-pkg-option=--force"
    
    81 80
                 , cabalExtraDirs libzstdIncludeDir libzstdLibraryDir
    
    82 81
                 ]