Cheng Shao pushed to branch wip/fix-clang64-split-sections at Glasgow Haskell Compiler / GHC

Commits:

27 changed files:

Changes:

  • compiler/GHC/Cmm.hs
    ... ... @@ -278,8 +278,8 @@ data SectionProtection
    278 278
       deriving (Eq)
    
    279 279
     
    
    280 280
     -- | Should a data in this section be considered constant at runtime
    
    281
    -sectionProtection :: Section -> SectionProtection
    
    282
    -sectionProtection (Section t _) = case t of
    
    281
    +sectionProtection :: SectionType -> SectionProtection
    
    282
    +sectionProtection t = case t of
    
    283 283
         Text                    -> ReadOnlySection
    
    284 284
         ReadOnlyData            -> ReadOnlySection
    
    285 285
         RelocatableReadOnlyData -> WriteProtectedSection
    

  • compiler/GHC/Cmm/InitFini.hs
    ... ... @@ -2,6 +2,7 @@
    2 2
     module GHC.Cmm.InitFini
    
    3 3
         ( InitOrFini(..)
    
    4 4
         , isInitOrFiniArray
    
    5
    +    , isInitOrFiniSection
    
    5 6
         ) where
    
    6 7
     
    
    7 8
     import GHC.Prelude
    
    ... ... @@ -63,8 +64,8 @@ finalizer CmmDecl will be emitted per module.
    63 64
     data InitOrFini = IsInitArray | IsFiniArray
    
    64 65
     
    
    65 66
     isInitOrFiniArray :: RawCmmDecl -> Maybe (InitOrFini, [CLabel])
    
    66
    -isInitOrFiniArray (CmmData sect (CmmStaticsRaw _ lits))
    
    67
    -  | Just initOrFini <- isInitOrFiniSection sect
    
    67
    +isInitOrFiniArray (CmmData (Section t _) (CmmStaticsRaw _ lits))
    
    68
    +  | Just initOrFini <- isInitOrFiniSection t
    
    68 69
       = Just (initOrFini, map get_label lits)
    
    69 70
       where
    
    70 71
         get_label :: CmmStatic -> CLabel
    
    ... ... @@ -72,7 +73,7 @@ isInitOrFiniArray (CmmData sect (CmmStaticsRaw _ lits))
    72 73
         get_label static = pprPanic "isInitOrFiniArray: invalid entry" (ppr static)
    
    73 74
     isInitOrFiniArray _ = Nothing
    
    74 75
     
    
    75
    -isInitOrFiniSection :: Section -> Maybe InitOrFini
    
    76
    -isInitOrFiniSection (Section InitArray _) = Just IsInitArray
    
    77
    -isInitOrFiniSection (Section FiniArray _) = Just IsFiniArray
    
    76
    +isInitOrFiniSection :: SectionType -> Maybe InitOrFini
    
    77
    +isInitOrFiniSection InitArray = Just IsInitArray
    
    78
    +isInitOrFiniSection FiniArray = Just IsFiniArray
    
    78 79
     isInitOrFiniSection _                     = Nothing

  • compiler/GHC/CmmToAsm/AArch64/Ppr.hs
    ... ... @@ -19,6 +19,7 @@ import GHC.Cmm.Dataflow.Label
    19 19
     
    
    20 20
     import GHC.Cmm.BlockId
    
    21 21
     import GHC.Cmm.CLabel
    
    22
    +import GHC.Cmm.InitFini
    
    22 23
     
    
    23 24
     import GHC.Types.Unique ( pprUniqueAlways, getUnique )
    
    24 25
     import GHC.Platform
    
    ... ... @@ -28,9 +29,7 @@ import GHC.Utils.Panic
    28 29
     
    
    29 30
     pprNatCmmDecl :: IsDoc doc => NCGConfig -> NatCmmDecl RawCmmStatics Instr -> doc
    
    30 31
     pprNatCmmDecl config (CmmData section dats) =
    
    31
    -  let platform = ncgPlatform config
    
    32
    -  in
    
    33
    -  pprSectionAlign config section $$ pprDatas platform dats
    
    32
    +  pprSectionAlign config section $$ pprDatas config dats
    
    34 33
     
    
    35 34
     pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) =
    
    36 35
       let platform = ncgPlatform config
    
    ... ... @@ -91,9 +90,20 @@ pprAlignForSection _platform _seg
    91 90
     --     .balign 8
    
    92 91
     --
    
    93 92
     pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
    
    94
    -pprSectionAlign config sec@(Section seg _) =
    
    93
    +pprSectionAlign config sec@(Section seg suffix) =
    
    95 94
         line (pprSectionHeader config sec)
    
    95
    +    $$ coffSplitSectionComdatKey
    
    96 96
         $$ pprAlignForSection (ncgPlatform config) seg
    
    97
    +  where
    
    98
    +    platform = ncgPlatform config
    
    99
    +    -- See Note [Split sections on COFF objects]
    
    100
    +    coffSplitSectionComdatKey
    
    101
    +      | OSMinGW32 <- platformOS platform
    
    102
    +      , ncgSplitSections config
    
    103
    +      , Nothing <- isInitOrFiniSection seg
    
    104
    +      = line (pprCOFFComdatKey platform suffix <> colon)
    
    105
    +      | otherwise
    
    106
    +      = empty
    
    97 107
     
    
    98 108
     -- | Output the ELF .size directive.
    
    99 109
     pprSizeDecl :: IsDoc doc => Platform -> CLabel -> doc
    
    ... ... @@ -136,20 +146,26 @@ pprBasicBlock platform with_dwarf info_env (BasicBlock blockid instrs)
    136 146
           (l@LOCATION{} : _) -> pprInstr platform l
    
    137 147
           _other             -> empty
    
    138 148
     
    
    139
    -pprDatas :: IsDoc doc => Platform -> RawCmmStatics -> doc
    
    149
    +pprDatas :: IsDoc doc => NCGConfig -> RawCmmStatics -> doc
    
    140 150
     -- See Note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel".
    
    141
    -pprDatas platform (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
    
    151
    +pprDatas config (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _])
    
    142 152
       | lbl == mkIndStaticInfoLabel
    
    143 153
       , let labelInd (CmmLabelOff l _) = Just l
    
    144 154
             labelInd (CmmLabel l) = Just l
    
    145 155
             labelInd _ = Nothing
    
    146 156
       , Just ind' <- labelInd ind
    
    147 157
       , alias `mayRedirectTo` ind'
    
    158
    +  -- See Note [Split sections on COFF objects]
    
    159
    +  , not $ platformOS platform == OSMinGW32 && ncgSplitSections config
    
    148 160
       = pprGloblDecl platform alias
    
    149 161
         $$ line (text ".equiv" <+> pprAsmLabel platform alias <> comma <> pprAsmLabel platform ind')
    
    162
    +    where
    
    163
    +      platform = ncgPlatform config
    
    150 164
     
    
    151
    -pprDatas platform (CmmStaticsRaw lbl dats)
    
    165
    +pprDatas config (CmmStaticsRaw lbl dats)
    
    152 166
       = vcat (pprLabel platform lbl : map (pprData platform) dats)
    
    167
    +    where
    
    168
    +      platform = ncgPlatform config
    
    153 169
     
    
    154 170
     pprData :: IsDoc doc => Platform -> CmmStatic -> doc
    
    155 171
     pprData _platform (CmmString str) = line (pprString str)
    

  • compiler/GHC/CmmToAsm/Ppr.hs
    1 1
     {-# LANGUAGE MagicHash #-}
    
    2
    +{-# LANGUAGE MultiWayIf #-}
    
    2 3
     
    
    3 4
     -----------------------------------------------------------------------------
    
    4 5
     --
    
    ... ... @@ -14,6 +15,7 @@ module GHC.CmmToAsm.Ppr (
    14 15
             pprASCII,
    
    15 16
             pprString,
    
    16 17
             pprFileEmbed,
    
    18
    +        pprCOFFComdatKey,
    
    17 19
             pprSectionHeader
    
    18 20
     )
    
    19 21
     
    
    ... ... @@ -23,6 +25,7 @@ import GHC.Prelude
    23 25
     
    
    24 26
     import GHC.Utils.Asm
    
    25 27
     import GHC.Cmm.CLabel
    
    28
    +import GHC.Cmm.InitFini
    
    26 29
     import GHC.Cmm
    
    27 30
     import GHC.CmmToAsm.Config
    
    28 31
     import GHC.Utils.Outputable as SDoc
    
    ... ... @@ -220,8 +223,8 @@ pprGNUSectionHeader config t suffix =
    220 223
                         | otherwise -> text ".rodata"
    
    221 224
           RelocatableReadOnlyData | OSMinGW32 <- platformOS platform
    
    222 225
                                     -- Concept does not exist on Windows,
    
    223
    -                                -- So map these to R/O data.
    
    224
    -                                          -> text ".rdata$rel.ro"
    
    226
    +                                -- So map these to data.
    
    227
    +                                          -> text ".data"
    
    225 228
                                   | otherwise -> text ".data.rel.ro"
    
    226 229
           UninitialisedData -> text ".bss"
    
    227 230
           InitArray
    
    ... ... @@ -240,24 +243,79 @@ pprGNUSectionHeader config t suffix =
    240 243
             | OSMinGW32 <- platformOS platform
    
    241 244
                         -> text ".rdata"
    
    242 245
             | otherwise -> text ".ipe"
    
    243
    -    flags = case t of
    
    244
    -      Text
    
    245
    -        | OSMinGW32 <- platformOS platform, splitSections
    
    246
    -                    -> text ",\"xr\""
    
    247
    -        | splitSections
    
    248
    -                    -> text ",\"ax\"," <> sectionType platform "progbits"
    
    249
    -      CString
    
    250
    -        | OSMinGW32 <- platformOS platform
    
    251
    -                    -> empty
    
    252
    -        | otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
    
    253
    -      IPE
    
    254
    -        | OSMinGW32 <- platformOS platform
    
    255
    -                    -> empty
    
    256
    -        | otherwise -> text ",\"a\"," <> sectionType platform "progbits"
    
    257
    -      _ -> empty
    
    246
    +    flags
    
    247
    +      -- See
    
    248
    +      -- https://github.com/llvm/llvm-project/blob/llvmorg-21.1.8/lld/COFF/Chunks.cpp#L54
    
    249
    +      -- and https://llvm.org/docs/Extensions.html#section-directive.
    
    250
    +      -- LLD COFF backend gc-sections only work on COMDAT sections so
    
    251
    +      -- we need to mark it as a COMDAT section. You can use clang64
    
    252
    +      -- toolchain to compile small examples with
    
    253
    +      -- `-ffunction-sections -fdata-sections -S` to see these section
    
    254
    +      -- headers in the wild. Also see Note [Split sections on COFF objects]
    
    255
    +      -- below.
    
    256
    +      | OSMinGW32 <- platformOS platform,
    
    257
    +        splitSections =
    
    258
    +          if
    
    259
    +            | Just _ <- isInitOrFiniSection t -> text ",\"dw\""
    
    260
    +            | otherwise ->
    
    261
    +                let coff_section_flags
    
    262
    +                      | Text <- t = "xr"
    
    263
    +                      | UninitialisedData <- t = "bw"
    
    264
    +                      | ReadOnlySection <- sectionProtection t = "dr"
    
    265
    +                      | otherwise = "dw"
    
    266
    +                 in hcat
    
    267
    +                      [ text ",\"",
    
    268
    +                        text coff_section_flags,
    
    269
    +                        text "\",one_only,",
    
    270
    +                        pprCOFFComdatKey platform suffix
    
    271
    +                      ]
    
    272
    +      | otherwise =
    
    273
    +          case t of
    
    274
    +            Text
    
    275
    +              | splitSections
    
    276
    +                          -> text ",\"ax\"," <> sectionType platform "progbits"
    
    277
    +            CString
    
    278
    +              | OSMinGW32 <- platformOS platform
    
    279
    +                          -> empty
    
    280
    +              | otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
    
    281
    +            IPE
    
    282
    +              | OSMinGW32 <- platformOS platform
    
    283
    +                          -> empty
    
    284
    +              | otherwise -> text ",\"a\"," <> sectionType platform "progbits"
    
    285
    +            _ -> empty
    
    258 286
     {-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> SDoc #-}
    
    259 287
     {-# SPECIALIZE pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
    
    260 288
     
    
    289
    +-- | Note [Split sections on COFF objects]
    
    290
    +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    291
    +--
    
    292
    +-- On Windows/COFF, LLD's gc-sections only works on COMDAT sections,
    
    293
    +-- so we mark split sections as COMDAT and need to provide a unique
    
    294
    +-- "key" symbol.
    
    295
    +--
    
    296
    +-- Important: We must not use a dot-prefixed local label (e.g.
    
    297
    +-- @.L...@) as the COMDAT key symbol, because LLVM's COFF assembler
    
    298
    +-- treats dot-prefixed COMDAT key symbols specially and forces them to
    
    299
    +-- have value 0 (the beginning of the section). That breaks
    
    300
    +-- @tablesNextToCode@, where the info label is intentionally placed
    
    301
    +-- after the info table data (at a non-zero offset).
    
    302
    +--
    
    303
    +-- Therefore we generate a non-dot-prefixed key symbol derived from
    
    304
    +-- the section suffix, and (see arch-specific 'pprSectionAlign') we
    
    305
    +-- emit a label definition for it at the beginning of the section.
    
    306
    +--
    
    307
    +-- ctor/dtor sections are specially treated; they must be emitted as
    
    308
    +-- regular data sections, otherwise LLD will drop them.
    
    309
    +--
    
    310
    +-- Note that we must not emit .equiv directives for COMDAT sections in
    
    311
    +-- COFF objects, they seriously confuse LLD and we end up with access
    
    312
    +-- violations at runtimes.
    
    313
    +pprCOFFComdatKey :: IsLine doc => Platform -> CLabel -> doc
    
    314
    +pprCOFFComdatKey platform suffix =
    
    315
    +  text "__ghc_coff_comdat_" <> pprAsmLabel platform suffix
    
    316
    +{-# SPECIALIZE pprCOFFComdatKey :: Platform -> CLabel -> SDoc #-}
    
    317
    +{-# SPECIALIZE pprCOFFComdatKey :: Platform -> CLabel -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable
    
    318
    +
    
    261 319
     -- XCOFF doesn't support relocating label-differences, so we place all
    
    262 320
     -- RO sections into .text[PR] sections
    
    263 321
     pprXcoffSectionHeader :: IsLine doc => SectionType -> doc
    

  • compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
    ... ... @@ -107,7 +107,7 @@ symKindFromCLabel lbl
    107 107
     -- | Calculate a data section's kind, see haddock docs of
    
    108 108
     -- 'DataSectionKind' for more explanation.
    
    109 109
     dataSectionKindFromCmmSection :: Section -> DataSectionKind
    
    110
    -dataSectionKindFromCmmSection s = case sectionProtection s of
    
    110
    +dataSectionKindFromCmmSection (Section t _) = case sectionProtection t of
    
    111 111
       ReadWriteSection -> SectionData
    
    112 112
       _ -> SectionROData
    
    113 113
     
    

  • compiler/GHC/CmmToAsm/X86/Ppr.hs
    ... ... @@ -31,6 +31,7 @@ import GHC.Cmm hiding (topInfoTable)
    31 31
     import GHC.Cmm.Dataflow.Label
    
    32 32
     import GHC.Cmm.BlockId
    
    33 33
     import GHC.Cmm.CLabel
    
    34
    +import GHC.Cmm.InitFini
    
    34 35
     import GHC.Cmm.DebugBlock (pprUnwindTable)
    
    35 36
     
    
    36 37
     import GHC.Types.Basic (Alignment, mkAlignment, alignmentBytes)
    
    ... ... @@ -195,8 +196,12 @@ pprDatas config (_, CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticL
    195 196
             labelInd _ = Nothing
    
    196 197
       , Just ind' <- labelInd ind
    
    197 198
       , alias `mayRedirectTo` ind'
    
    199
    +  -- See Note [Split sections on COFF objects]
    
    200
    +  , not $ platformOS platform == OSMinGW32 && ncgSplitSections config
    
    198 201
       = pprGloblDecl (ncgPlatform config) alias
    
    199 202
         $$ line (text ".equiv" <+> pprAsmLabel (ncgPlatform config) alias <> comma <> pprAsmLabel (ncgPlatform config) ind')
    
    203
    +    where
    
    204
    +      platform = ncgPlatform config
    
    200 205
     
    
    201 206
     pprDatas config (align, (CmmStaticsRaw lbl dats))
    
    202 207
      = vcat (pprAlign platform align : pprLabel platform lbl : map (pprData config) dats)
    
    ... ... @@ -526,9 +531,20 @@ pprAddr platform (AddrBaseIndex base index displacement)
    526 531
     
    
    527 532
     -- | Print section header and appropriate alignment for that section.
    
    528 533
     pprSectionAlign :: IsDoc doc => NCGConfig -> Section -> doc
    
    529
    -pprSectionAlign config sec@(Section seg _) =
    
    534
    +pprSectionAlign config sec@(Section seg suffix) =
    
    530 535
         line (pprSectionHeader config sec) $$
    
    536
    +    coffSplitSectionComdatKey $$
    
    531 537
         pprAlignForSection (ncgPlatform config) seg
    
    538
    +  where
    
    539
    +    platform = ncgPlatform config
    
    540
    +    -- See Note [Split sections on COFF objects]
    
    541
    +    coffSplitSectionComdatKey
    
    542
    +      | OSMinGW32 <- platformOS platform
    
    543
    +      , ncgSplitSections config
    
    544
    +      , Nothing <- isInitOrFiniSection seg
    
    545
    +      = line (pprCOFFComdatKey platform suffix <> colon)
    
    546
    +      | otherwise
    
    547
    +      = empty
    
    532 548
     
    
    533 549
     -- | Print appropriate alignment for the given section type.
    
    534 550
     pprAlignForSection :: IsDoc doc => Platform -> SectionType -> doc
    

  • compiler/GHC/CmmToC.hs
    ... ... @@ -121,7 +121,7 @@ pprTop platform = \case
    121 121
         pprDataExterns platform lits $$
    
    122 122
         pprWordArray platform (isSecConstant section) lbl lits
    
    123 123
       where
    
    124
    -    isSecConstant section = case sectionProtection section of
    
    124
    +    isSecConstant (Section t _) = case sectionProtection t of
    
    125 125
           ReadOnlySection -> True
    
    126 126
           WriteProtectedSection -> True
    
    127 127
           _ -> False
    

  • compiler/GHC/CmmToLlvm/Data.hs
    ... ... @@ -75,7 +75,7 @@ genLlvmData (sect, statics)
    75 75
                     IsFiniArray -> fsLit "llvm.global_dtors"
    
    76 76
         in genGlobalLabelArray var clbls
    
    77 77
     
    
    78
    -genLlvmData (sec, CmmStaticsRaw lbl xs) = do
    
    78
    +genLlvmData (sec@(Section t _), CmmStaticsRaw lbl xs) = do
    
    79 79
         label <- strCLabel_llvm lbl
    
    80 80
         static <- mapM genData xs
    
    81 81
         lmsec <- llvmSection sec
    
    ... ... @@ -92,7 +92,7 @@ genLlvmData (sec, CmmStaticsRaw lbl xs) = do
    92 92
                                                         then Just 2 else Just 1
    
    93 93
                                 Section Data _    -> Just $ platformWordSizeInBytes platform
    
    94 94
                                 _                 -> Nothing
    
    95
    -        const          = if sectionProtection sec == ReadOnlySection
    
    95
    +        const          = if sectionProtection t == ReadOnlySection
    
    96 96
                                 then Constant else Global
    
    97 97
             varDef         = LMGlobalVar label tyAlias link lmsec align const
    
    98 98
             globDef        = LMGlobal varDef struct
    

  • docs/users_guide/exts/pragmas.rst
    ... ... @@ -58,10 +58,9 @@ prefixing it with "``-X``"; for example ``-XForeignFunctionInterface``.
    58 58
     
    
    59 59
     A list of all supported language extensions can be obtained by invoking
    
    60 60
     ``ghc --supported-extensions`` (see :ghc-flag:`--supported-extensions`).
    
    61
    +Alternatively see :ref:`table`.
    
    61 62
     
    
    62
    -Any extension from the ``Extension`` type defined in
    
    63
    -:cabal-ref:`Language.Haskell.Extension.` may be used. GHC will report an error
    
    64
    -if any of the requested extensions are not supported.
    
    63
    +GHC will report an error if any of the requested extensions are not supported.
    
    65 64
     
    
    66 65
     .. _options-pragma:
    
    67 66
     
    

  • docs/users_guide/exts/table.rst
    1
    +.. _table:
    
    2
    +
    
    1 3
     Overview of all language extensions
    
    2 4
     -----------------------------------
    
    3 5
     
    

  • 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
                 ]