Rodrigo Mesquita pushed to branch wip/romes/26227 at Glasgow Haskell Compiler / GHC

Commits:

19 changed files:

Changes:

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -3501,6 +3501,7 @@ compilerInfo dflags
    3501 3501
            ("target has libm", queryBool tgtHasLibm),
    
    3502 3502
            ("target has .ident directive", queryBool tgtSupportsIdentDirective),
    
    3503 3503
            ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols),
    
    3504
    +       ("target RTS linker only supports shared libraries", queryBool tgtRTSLinkerOnlySupportsSharedLibs)
    
    3504 3505
            ("Unregisterised", queryBool tgtUnregisterised),
    
    3505 3506
            ("LLVM target", query tgtLlvmTarget),
    
    3506 3507
            ("LLVM llc command", queryCmdMaybe id tgtLlc),
    
    ... ... @@ -3508,7 +3509,8 @@ compilerInfo dflags
    3508 3509
            ("LLVM llvm-as command", queryCmdMaybe id tgtLlvmAs),
    
    3509 3510
            ("LLVM llvm-as flags", queryFlagsMaybe id tgtLlvmAs),
    
    3510 3511
            ("Tables next to code", queryBool tgtTablesNextToCode),
    
    3511
    -       ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore)
    
    3512
    +       ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore),
    
    3513
    +       ("RTS expects libdw", queryBool (isJust . tgtRTSWithLibdw))
    
    3512 3514
           ] ++
    
    3513 3515
           [("Project version",             projectVersion dflags),
    
    3514 3516
            ("Project Git commit id",       cProjectGitCommitId),
    
    ... ... @@ -3526,6 +3528,9 @@ compilerInfo dflags
    3526 3528
            ("target os string",            stringEncodeOS (platformOS (targetPlatform dflags))),
    
    3527 3529
            ("target arch string",          stringEncodeArch (platformArch (targetPlatform dflags))),
    
    3528 3530
            ("target word size in bits",    show (platformWordSizeInBits (targetPlatform dflags))),
    
    3531
    +       -- keep "duplicate" of "Have interpreter" for backwards compatibility,
    
    3532
    +       -- since we used to show both...
    
    3533
    +       ("Use interpreter",             showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
    
    3529 3534
            ("Have interpreter",            showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
    
    3530 3535
            ("Object splitting supported",  showBool False),
    
    3531 3536
            ("Have native code generator",  showBool $ platformNcgSupported platform),
    
    ... ... @@ -3545,6 +3550,7 @@ compilerInfo dflags
    3545 3550
            -- If true, we require that the 'id' field in installed package info
    
    3546 3551
            -- match what is passed to the @-this-unit-id@ flag for modules
    
    3547 3552
            -- built in it
    
    3553
    +       ("Support SMP", queryBool tgtSupportsSMP),
    
    3548 3554
            ("Requires unified installed package IDs", "YES"),
    
    3549 3555
            -- Whether or not we support the @-this-package-key@ flag.  Prefer
    
    3550 3556
            -- "Uses unit IDs" over it. We still say yes even if @-this-package-key@
    

  • compiler/GHC/Settings/IO.hs
    ... ... @@ -146,7 +146,6 @@ initSettings top_dir = do
    146 146
             pure (ld_r_path, map Option ld_r_args)
    
    147 147
           iserv_prog   = libexec "ghc-iserv"
    
    148 148
     
    
    149
    -  targetRTSLinkerOnlySupportsSharedLibs <- getBooleanSetting "target RTS linker only supports shared libraries"
    
    150 149
       ghcWithInterpreter <- getBooleanSetting "Use interpreter"
    
    151 150
     
    
    152 151
       baseUnitId <- getSetting_raw "base unit-id"
    
    ... ... @@ -231,7 +230,7 @@ initSettings top_dir = do
    231 230
           , platformMisc_ghcWithInterpreter = ghcWithInterpreter
    
    232 231
           , platformMisc_libFFI = tgtUseLibffiForAdjustors target
    
    233 232
           , platformMisc_llvmTarget = tgtLlvmTarget target
    
    234
    -      , platformMisc_targetRTSLinkerOnlySupportsSharedLibs = targetRTSLinkerOnlySupportsSharedLibs
    
    233
    +      , platformMisc_targetRTSLinkerOnlySupportsSharedLibs = tgtRTSLinkerOnlySupportsSharedLibs target
    
    235 234
           }
    
    236 235
     
    
    237 236
         , sRawSettings    = settingsList
    

  • hadrian/bindist/Makefile
    ... ... @@ -86,11 +86,8 @@ WrapperBinsDir=${bindir}
    86 86
     lib/settings : config.mk
    
    87 87
     	@rm -f $@
    
    88 88
     	@echo '[("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    89
    -	@echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@
    
    90 89
     	@echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@
    
    91
    -	@echo ',("Support SMP", "$(GhcWithSMP)")' >> $@
    
    92 90
     	@echo ',("RTS ways", "$(GhcRTSWays)")' >> $@
    
    93
    -	@echo ',("RTS expects libdw", "$(GhcRtsWithLibdw)")' >> $@
    
    94 91
     	@echo ',("Relative Global Package DB", "package.conf.d")' >> $@
    
    95 92
     	@echo ',("base unit-id", "$(BaseUnitId)")' >> $@
    
    96 93
     	@echo "]" >> $@
    

  • hadrian/bindist/config.mk.in
    ... ... @@ -172,7 +172,7 @@ UseLibffiForAdjustors=@UseLibffiForAdjustors@
    172 172
     
    
    173 173
     # GHC needs arch-specific tweak at least in
    
    174 174
     #     rts/Libdw.c:set_initial_registers()
    
    175
    -GhcRtsWithLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO))
    
    175
    +UseLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO))
    
    176 176
     
    
    177 177
     #-----------------------------------------------------------------------------
    
    178 178
     # Settings
    

  • hadrian/cfg/default.host.target.in
    ... ... @@ -13,6 +13,7 @@ Target
    13 13
     , tgtTablesNextToCode = True
    
    14 14
     , tgtUseLibffiForAdjustors = True
    
    15 15
     , tgtHasLibm = True
    
    16
    +, tgtRTSWithLibdw = Nothing
    
    16 17
     , tgtCCompiler = Cc {ccProgram = Program {prgPath = "@CC_STAGE0@", prgFlags = @CONF_CC_OPTS_STAGE0List@}}
    
    17 18
     , tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@CC_STAGE0@", prgFlags = @CONF_CXX_OPTS_STAGE0List@}}
    
    18 19
     , tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@CPPCmd_STAGE0@", prgFlags = @CONF_CPP_OPTS_STAGE0List@}}
    

  • hadrian/cfg/default.target.in
    ... ... @@ -13,6 +13,7 @@ Target
    13 13
     , tgtTablesNextToCode = @TablesNextToCodeBool@
    
    14 14
     , tgtUseLibffiForAdjustors = @UseLibffiForAdjustorsBool@
    
    15 15
     , tgtHasLibm = @TargetHasLibmBool@
    
    16
    +, tgtRTSWithLibdw = @UseLibdwMaybeLibrary@
    
    16 17
     , tgtCCompiler = Cc {ccProgram = Program {prgPath = "@CC@", prgFlags = @CONF_CC_OPTS_STAGE2List@}}
    
    17 18
     , tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@CXX@", prgFlags = @CONF_CXX_OPTS_STAGE2List@}}
    
    18 19
     , tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@CPPCmd@", prgFlags = @CONF_CPP_OPTS_STAGE2List@}}
    

  • hadrian/cfg/system.config.in
    ... ... @@ -99,9 +99,6 @@ use-system-ffi = @UseSystemLibFFI@
    99 99
     ffi-include-dir   = @FFIIncludeDir@
    
    100 100
     ffi-lib-dir       = @FFILibDir@
    
    101 101
     
    
    102
    -libdw-include-dir   = @LibdwIncludeDir@
    
    103
    -libdw-lib-dir       = @LibdwLibDir@
    
    104
    -
    
    105 102
     libnuma-include-dir   = @LibNumaIncludeDir@
    
    106 103
     libnuma-lib-dir       = @LibNumaLibDir@
    
    107 104
     
    
    ... ... @@ -111,7 +108,6 @@ libzstd-lib-dir = @LibZstdLibDir@
    111 108
     # Optional Dependencies:
    
    112 109
     #=======================
    
    113 110
     
    
    114
    -use-lib-dw        = @UseLibdw@
    
    115 111
     use-lib-zstd      = @UseLibZstd@
    
    116 112
     static-lib-zstd   = @UseStaticLibZstd@
    
    117 113
     use-lib-numa      = @UseLibNuma@
    

  • hadrian/src/Oracles/Flag.hs
    ... ... @@ -7,7 +7,7 @@ module Oracles.Flag (
    7 7
         targetRTSLinkerOnlySupportsSharedLibs,
    
    8 8
         targetSupportsThreadedRts,
    
    9 9
         targetSupportsSMP,
    
    10
    -    useLibffiForAdjustors,
    
    10
    +    useLibffiForAdjustors, useLibdw,
    
    11 11
         arSupportsDashL,
    
    12 12
         arSupportsAtFile
    
    13 13
         ) where
    
    ... ... @@ -29,7 +29,6 @@ data Flag = CrossCompiling
    29 29
               | UseSystemFfi
    
    30 30
               | BootstrapThreadedRts
    
    31 31
               | BootstrapEventLoggingRts
    
    32
    -          | UseLibdw
    
    33 32
               | UseLibnuma
    
    34 33
               | UseLibzstd
    
    35 34
               | StaticLibzstd
    
    ... ... @@ -53,7 +52,6 @@ flag f = do
    53 52
                 UseSystemFfi         -> "use-system-ffi"
    
    54 53
                 BootstrapThreadedRts -> "bootstrap-threaded-rts"
    
    55 54
                 BootstrapEventLoggingRts -> "bootstrap-event-logging-rts"
    
    56
    -            UseLibdw             -> "use-lib-dw"
    
    57 55
                 UseLibnuma           -> "use-lib-numa"
    
    58 56
                 UseLibzstd           -> "use-lib-zstd"
    
    59 57
                 StaticLibzstd        -> "static-lib-zstd"
    
    ... ... @@ -82,23 +80,8 @@ platformSupportsGhciObjects = do
    82 80
         only_shared_libs <- targetRTSLinkerOnlySupportsSharedLibs
    
    83 81
         pure $ has_merge_objs && not only_shared_libs
    
    84 82
     
    
    85
    --- | Does the target RTS linker only support loading shared libraries?
    
    86
    --- If true, this has several implications:
    
    87
    --- 1. The GHC driver must not do loadArchive/loadObj etc and must
    
    88
    ---    always do loadDLL, regardless of whether host GHC is dynamic or
    
    89
    ---    not.
    
    90
    --- 2. The GHC driver will always enable -dynamic-too when compiling
    
    91
    ---    vanilla way with TH codegen requirement.
    
    92
    --- 3. ghci will always enforce dynamic ways even if -dynamic or
    
    93
    ---    -dynamic-too is not explicitly passed.
    
    94
    --- 4. Cabal must not build ghci objects since it's not supported by
    
    95
    ---    the target.
    
    96
    --- 5. The testsuite driver will use dyn way for TH/ghci tests even
    
    97
    ---    when host GHC is static.
    
    98
    --- 6. TH/ghci doesn't work if stage1 is built without shared libraries
    
    99
    ---    (e.g. quickest/fully_static).
    
    100 83
     targetRTSLinkerOnlySupportsSharedLibs :: Action Bool
    
    101
    -targetRTSLinkerOnlySupportsSharedLibs = anyTargetArch [ ArchWasm32 ]
    
    84
    +targetRTSLinkerOnlySupportsSharedLibs = queryTargetTarget Toolchain.tgtRTSLinkerOnlySupportsSharedLibs
    
    102 85
     
    
    103 86
     arSupportsDashL :: Stage -> Action Bool
    
    104 87
     arSupportsDashL stage = Toolchain.arSupportsDashL . tgtAr <$> targetStage stage
    
    ... ... @@ -123,27 +106,10 @@ targetSupportsThreadedRts = do
    123 106
     
    
    124 107
     -- | Does the target support the -N RTS flag?
    
    125 108
     targetSupportsSMP :: Action Bool
    
    126
    -targetSupportsSMP = do
    
    127
    -  unreg <- queryTargetTarget tgtUnregisterised
    
    128
    -  armVer <- targetArmVersion
    
    129
    -  goodArch <- (||) <$>
    
    130
    -              anyTargetArch [ ArchX86
    
    131
    -                            , ArchX86_64
    
    132
    -                            , ArchPPC
    
    133
    -                            , ArchPPC_64 ELF_V1
    
    134
    -                            , ArchPPC_64 ELF_V2
    
    135
    -                            , ArchAArch64
    
    136
    -                            , ArchS390X
    
    137
    -                            , ArchRISCV64
    
    138
    -                            , ArchLoongArch64 ] <*> isArmTarget
    
    139
    -  if   -- The THREADED_RTS requires `BaseReg` to be in a register and the
    
    140
    -       -- Unregisterised mode doesn't allow that.
    
    141
    -     | unreg                -> return False
    
    142
    -       -- We don't support load/store barriers pre-ARMv7. See #10433.
    
    143
    -     | Just ver <- armVer
    
    144
    -     , ver < ARMv7          -> return False
    
    145
    -     | goodArch             -> return True
    
    146
    -     | otherwise            -> return False
    
    109
    +targetSupportsSMP = queryTargetTarget Toolchain.tgtSupportsSMP
    
    147 110
     
    
    148 111
     useLibffiForAdjustors :: Action Bool
    
    149 112
     useLibffiForAdjustors = queryTargetTarget tgtUseLibffiForAdjustors
    
    113
    +
    
    114
    +useLibdw :: Action Bool
    
    115
    +useLibdw = queryTargetTarget (isJust . tgtRTSWithLibdw)

  • hadrian/src/Oracles/Setting.hs
    ... ... @@ -54,8 +54,6 @@ data Setting = CursesIncludeDir
    54 54
                  | GmpLibDir
    
    55 55
                  | IconvIncludeDir
    
    56 56
                  | IconvLibDir
    
    57
    -             | LibdwIncludeDir
    
    58
    -             | LibdwLibDir
    
    59 57
                  | LibnumaIncludeDir
    
    60 58
                  | LibnumaLibDir
    
    61 59
                  | LibZstdIncludeDir
    
    ... ... @@ -94,8 +92,6 @@ setting key = lookupSystemConfig $ case key of
    94 92
         GmpLibDir          -> "gmp-lib-dir"
    
    95 93
         IconvIncludeDir    -> "iconv-include-dir"
    
    96 94
         IconvLibDir        -> "iconv-lib-dir"
    
    97
    -    LibdwIncludeDir    -> "libdw-include-dir"
    
    98
    -    LibdwLibDir        -> "libdw-lib-dir"
    
    99 95
         LibnumaIncludeDir  -> "libnuma-include-dir"
    
    100 96
         LibnumaLibDir      -> "libnuma-lib-dir"
    
    101 97
         LibZstdIncludeDir  -> "libzstd-include-dir"
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -432,7 +432,7 @@ bindistRules = do
    432 432
         , interpolateVar "TargetWordBigEndian" $ getTarget isBigEndian
    
    433 433
         , interpolateVar "TargetWordSize" $ getTarget wordSize
    
    434 434
         , interpolateVar "Unregisterised" $ yesNo <$> getTarget tgtUnregisterised
    
    435
    -    , interpolateVar "UseLibdw" $ fmap yesNo $ interp $ getFlag UseLibdw
    
    435
    +    , interpolateVar "UseLibdw" $ yesNo <$> getTarget (isJust . tgtRTSWithLibdw)
    
    436 436
         , interpolateVar "UseLibffiForAdjustors" $ yesNo <$> getTarget tgtUseLibffiForAdjustors
    
    437 437
         , interpolateVar "GhcWithSMP" $ yesNo <$> targetSupportsSMP
    
    438 438
         , interpolateVar "BaseUnitId" $ pkgUnitId Stage1 base
    
    ... ... @@ -484,11 +484,8 @@ generateSettings settingsFile = do
    484 484
     
    
    485 485
         settings <- traverse sequence $
    
    486 486
             [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
    
    487
    -        , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs)
    
    488 487
             , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
    
    489
    -        , ("Support SMP", expr $ yesNo <$> targetSupportsSMP)
    
    490 488
             , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
    
    491
    -        , ("RTS expects libdw", yesNo <$> getFlag UseLibdw)
    
    492 489
             , ("Relative Global Package DB", pure rel_pkg_db)
    
    493 490
             , ("base unit-id", pure base_unit_id)
    
    494 491
             ]
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -8,6 +8,7 @@ import Packages
    8 8
     import Settings
    
    9 9
     import Settings.Builders.Common (wayCcArgs)
    
    10 10
     
    
    11
    +import qualified GHC.Toolchain.Library as Lib
    
    11 12
     import GHC.Toolchain.Target
    
    12 13
     import GHC.Platform.ArchOS
    
    13 14
     import Data.Version.Extra
    
    ... ... @@ -304,8 +305,8 @@ rtsPackageArgs = package rts ? do
    304 305
         useSystemFfi   <- getFlag UseSystemFfi
    
    305 306
         ffiIncludeDir  <- getSetting FfiIncludeDir
    
    306 307
         ffiLibraryDir  <- getSetting FfiLibDir
    
    307
    -    libdwIncludeDir   <- getSetting LibdwIncludeDir
    
    308
    -    libdwLibraryDir   <- getSetting LibdwLibDir
    
    308
    +    libdwIncludeDir   <- queryTarget (Lib.includePath <=< tgtRTSWithLibdw)
    
    309
    +    libdwLibraryDir   <- queryTarget (Lib.libraryPath <=< tgtRTSWithLibdw)
    
    309 310
         libnumaIncludeDir <- getSetting LibnumaIncludeDir
    
    310 311
         libnumaLibraryDir <- getSetting LibnumaLibDir
    
    311 312
         libzstdIncludeDir <- getSetting LibZstdIncludeDir
    
    ... ... @@ -443,7 +444,7 @@ rtsPackageArgs = package rts ? do
    443 444
               , flag UseLibpthread              `cabalFlag` "need-pthread"
    
    444 445
               , flag UseLibbfd                  `cabalFlag` "libbfd"
    
    445 446
               , flag NeedLibatomic              `cabalFlag` "need-atomic"
    
    446
    -          , flag UseLibdw                   `cabalFlag` "libdw"
    
    447
    +          , useLibdw                        `cabalFlag` "libdw"
    
    447 448
               , flag UseLibnuma                 `cabalFlag` "libnuma"
    
    448 449
               , flag UseLibzstd                 `cabalFlag` "libzstd"
    
    449 450
               , flag StaticLibzstd              `cabalFlag` "static-libzstd"
    
    ... ... @@ -453,7 +454,7 @@ rtsPackageArgs = package rts ? do
    453 454
               , Debug `wayUnit` way             `cabalFlag` "find-ptr"
    
    454 455
               ]
    
    455 456
             , builder (Cabal Setup) ? mconcat
    
    456
    -              [ cabalExtraDirs libdwIncludeDir libdwLibraryDir
    
    457
    +              [ useLibdw ? cabalExtraDirs (fromMaybe "" libdwIncludeDir) (fromMaybe "" libdwLibraryDir)
    
    457 458
                   , cabalExtraDirs libnumaIncludeDir libnumaLibraryDir
    
    458 459
                   , cabalExtraDirs libzstdIncludeDir libzstdLibraryDir
    
    459 460
                   , useSystemFfi ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
    
    ... ... @@ -467,7 +468,7 @@ rtsPackageArgs = package rts ? do
    467 468
             , builder HsCpp ? pure
    
    468 469
               [ "-DTOP="             ++ show top ]
    
    469 470
     
    
    470
    -        , builder HsCpp ? flag UseLibdw ? arg "-DUSE_LIBDW" ]
    
    471
    +        , builder HsCpp ? useLibdw ? arg "-DUSE_LIBDW" ]
    
    471 472
     
    
    472 473
     -- Compile various performance-critical pieces *without* -fPIC -dynamic
    
    473 474
     -- even when building a shared library.  If we don't do this, then the
    

  • m4/fp_find_libdw.m4
    ... ... @@ -29,11 +29,11 @@ AC_DEFUN([FP_FIND_LIBDW],
    29 29
       AC_ARG_ENABLE(dwarf-unwind,
    
    30 30
         [AS_HELP_STRING([--enable-dwarf-unwind],
    
    31 31
           [Enable DWARF unwinding support in the runtime system via elfutils' libdw [default=no]])],
    
    32
    -    [],
    
    33
    -    [enable_dwarf_unwind=no])
    
    32
    +    [FP_CAPITALIZE_YES_NO(["$enableval"], [enable_dwarf_unwind])],
    
    33
    +    [enable_dwarf_unwind=NO])
    
    34 34
     
    
    35 35
       UseLibdw=NO
    
    36
    -  if test "$enable_dwarf_unwind" != "no" ; then
    
    36
    +  if test "$enable_dwarf_unwind" != "NO" ; then
    
    37 37
         CFLAGS2="$CFLAGS"
    
    38 38
         CFLAGS="$LIBDW_CFLAGS $CFLAGS"
    
    39 39
         LDFLAGS2="$LDFLAGS"
    
    ... ... @@ -43,7 +43,7 @@ AC_DEFUN([FP_FIND_LIBDW],
    43 43
           [AC_CHECK_LIB(dw, dwfl_attach_state,
    
    44 44
             [UseLibdw=YES])])
    
    45 45
     
    
    46
    -    if test "x:$enable_dwarf_unwind:$UseLibdw" = "x:yes:NO" ; then
    
    46
    +    if test "x:$enable_dwarf_unwind:$UseLibdw" = "x:YES:NO" ; then
    
    47 47
           AC_MSG_ERROR([Cannot find system libdw (required by --enable-dwarf-unwind)])
    
    48 48
         fi
    
    49 49
     
    

  • m4/ghc_toolchain.m4
    ... ... @@ -120,6 +120,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
    120 120
         ENABLE_GHC_TOOLCHAIN_ARG([tables-next-to-code], [$TablesNextToCode])
    
    121 121
         ENABLE_GHC_TOOLCHAIN_ARG([ld-override], [$enable_ld_override])
    
    122 122
         ENABLE_GHC_TOOLCHAIN_ARG([libffi-adjustors], [$UseLibffiForAdjustors])
    
    123
    +    ENABLE_GHC_TOOLCHAIN_ARG([dwarf-unwind], [$enable_dwarf_unwind])
    
    123 124
     
    
    124 125
         dnl We store USER_* variants of all user-specified flags to pass them over to ghc-toolchain.
    
    125 126
         ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-opt], [$USER_CONF_CC_OPTS_STAGE2], [$USER_CFLAGS])
    
    ... ... @@ -130,6 +131,8 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
    130 131
         ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$USER_HS_CPP_ARGS])
    
    131 132
         ADD_GHC_TOOLCHAIN_ARG([js-cpp-opt], [$USER_JS_CPP_ARGS])
    
    132 133
         ADD_GHC_TOOLCHAIN_ARG([cmm-cpp-opt], [$USER_CMM_CPP_ARGS])
    
    134
    +    ADD_GHC_TOOLCHAIN_ARG([libdw-includes], [$LibdwIncludeDir])
    
    135
    +    ADD_GHC_TOOLCHAIN_ARG([libdw-libraries], [$LibdwLibDir])
    
    133 136
     
    
    134 137
         INVOKE_GHC_TOOLCHAIN()
    
    135 138
     
    

  • m4/prep_target_file.m4
    ... ... @@ -78,6 +78,22 @@ AC_DEFUN([PREP_MAYBE_PROGRAM],[
    78 78
         AC_SUBST([$1MaybeProg])
    
    79 79
     ])
    
    80 80
     
    
    81
    +# PREP_MAYBE_LIBRARY
    
    82
    +# =========================
    
    83
    +#
    
    84
    +# Introduce a substitution [$1MaybeProg] with
    
    85
    +# * Nothing, if $$1 is empty or "NO"
    
    86
    +# * Just the library otherwise
    
    87
    +AC_DEFUN([PREP_MAYBE_LIBRARY],[
    
    88
    +    if test -z "$$1" || test "$$1" = "NO"; then
    
    89
    +        $1MaybeLibrary=Nothing
    
    90
    +    else
    
    91
    +        PREP_LIST([$2])
    
    92
    +        $1MaybeLibrary="Just (Library { libName = \"$2\", includePath = \"$3\", libraryPath = \"$4\" })"
    
    93
    +    fi
    
    94
    +    AC_SUBST([$1MaybeLibrary])
    
    95
    +])
    
    96
    +
    
    81 97
     # PREP_MAYBE_STRING
    
    82 98
     # =========================
    
    83 99
     #
    
    ... ... @@ -180,6 +196,10 @@ AC_DEFUN([PREP_TARGET_FILE],[
    180 196
         PREP_LIST([CONF_CXX_OPTS_STAGE2])
    
    181 197
         PREP_LIST([CONF_CC_OPTS_STAGE2])
    
    182 198
     
    
    199
    +    PREP_MAYBE_STRING([LibdwIncludeDir])
    
    200
    +    PREP_MAYBE_STRING([LibdwLibDir])
    
    201
    +    PREP_MAYBE_LIBRARY([UseLibdw], [dw], [$LibdwIncludeDirMaybeStr], [$LibdwLibDirMaybeStr])
    
    202
    +
    
    183 203
         dnl Host target
    
    184 204
         PREP_BOOLEAN([ArSupportsAtFile_STAGE0])
    
    185 205
         PREP_BOOLEAN([ArSupportsDashL_STAGE0])
    
    ... ... @@ -189,7 +209,6 @@ AC_DEFUN([PREP_TARGET_FILE],[
    189 209
         PREP_LIST([CONF_CXX_OPTS_STAGE0])
    
    190 210
         PREP_LIST([CONF_GCC_LINKER_OPTS_STAGE0])
    
    191 211
     
    
    192
    -
    
    193 212
         if test -z "$MergeObjsCmd"; then
    
    194 213
           MergeObjsCmdMaybe=Nothing
    
    195 214
         else
    

  • utils/ghc-toolchain/exe/Main.hs
    ... ... @@ -62,6 +62,12 @@ data Opts = Opts
    62 62
         -- see #23857 and #22550 for the very unfortunate story.
    
    63 63
         , optLd        :: ProgOpt
    
    64 64
         , optUnregisterised :: Maybe Bool
    
    65
    +
    
    66
    +    -- dwarf unwinding
    
    67
    +    , optDwarfUnwind :: Maybe Bool
    
    68
    +    , optLibdwIncludes :: Maybe FilePath
    
    69
    +    , optLibdwLibraries :: Maybe FilePath
    
    70
    +
    
    65 71
         , optTablesNextToCode :: Maybe Bool
    
    66 72
         , optUseLibFFIForAdjustors :: Maybe Bool
    
    67 73
         , optLdOverride :: Maybe Bool
    
    ... ... @@ -112,6 +118,9 @@ emptyOpts = Opts
    112 118
         , optOtool     = po0
    
    113 119
         , optInstallNameTool = po0
    
    114 120
         , optUnregisterised = Nothing
    
    121
    +    , optDwarfUnwind = Nothing
    
    122
    +    , optLibdwIncludes = Nothing
    
    123
    +    , optLibdwLibraries = Nothing
    
    115 124
         , optTablesNextToCode = Nothing
    
    116 125
         , optUseLibFFIForAdjustors = Nothing
    
    117 126
         , optLdOverride = Nothing
    
    ... ... @@ -157,13 +166,18 @@ _optOutput = Lens optOutput (\x o -> o {optOutput=x})
    157 166
     _optTargetPrefix :: Lens Opts (Maybe String)
    
    158 167
     _optTargetPrefix = Lens optTargetPrefix (\x o -> o {optTargetPrefix=x})
    
    159 168
     
    
    160
    -_optLocallyExecutable, _optUnregisterised, _optTablesNextToCode, _optUseLibFFIForAdjustors, _optLdOvveride :: Lens Opts (Maybe Bool)
    
    169
    +_optLocallyExecutable, _optUnregisterised, _optTablesNextToCode, _optUseLibFFIForAdjustors, _optLdOvveride, _optDwarfUnwind :: Lens Opts (Maybe Bool)
    
    161 170
     _optLocallyExecutable = Lens optLocallyExecutable (\x o -> o {optLocallyExecutable=x})
    
    162 171
     _optUnregisterised = Lens optUnregisterised (\x o -> o {optUnregisterised=x})
    
    172
    +_optDwarfUnwind = Lens optDwarfUnwind (\x o -> o {optDwarfUnwind=x})
    
    163 173
     _optTablesNextToCode = Lens optTablesNextToCode (\x o -> o {optTablesNextToCode=x})
    
    164 174
     _optUseLibFFIForAdjustors = Lens optUseLibFFIForAdjustors (\x o -> o {optUseLibFFIForAdjustors=x})
    
    165 175
     _optLdOvveride = Lens optLdOverride (\x o -> o {optLdOverride=x})
    
    166 176
     
    
    177
    +_optLibdwIncludes, _optLibdwLibraries :: Lens Opts (Maybe FilePath)
    
    178
    +_optLibdwIncludes = Lens optLibdwIncludes (\x o -> o {optLibdwIncludes=x})
    
    179
    +_optLibdwLibraries = Lens optLibdwLibraries (\x o -> o {optLibdwLibraries=x})
    
    180
    +
    
    167 181
     _optVerbosity :: Lens Opts Int
    
    168 182
     _optVerbosity = Lens optVerbosity (\x o -> o {optVerbosity=x})
    
    169 183
     
    
    ... ... @@ -185,6 +199,7 @@ options =
    185 199
         , enableDisable "libffi-adjustors" "the use of libffi for adjustors, even on platforms which have support for more efficient, native adjustor implementations." _optUseLibFFIForAdjustors
    
    186 200
         , enableDisable "ld-override" "override gcc's default linker" _optLdOvveride
    
    187 201
         , enableDisable "locally-executable" "the use of a target prefix which will be added to all tool names when searching for toolchain components" _optLocallyExecutable
    
    202
    +    , enableDisable "dwarf-unwind" "Enable DWARF unwinding support in the runtime system via elfutils' libdw" _optDwarfUnwind
    
    188 203
         ] ++
    
    189 204
         concat
    
    190 205
         [ progOpts "cc" "C compiler" _optCc
    
    ... ... @@ -206,6 +221,9 @@ options =
    206 221
         , progOpts "ld" "linker" _optLd
    
    207 222
         , progOpts "otool" "otool utility" _optOtool
    
    208 223
         , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool
    
    224
    +    ] ++
    
    225
    +    [ Option [] ["libdw-includes"] (ReqArg (set _optLibdwIncludes . Just) "PATH") "Look for libdw headers in this extra path"
    
    226
    +    , Option [] ["libdw-libraries"] (ReqArg (set _optLibdwLibraries . Just) "PATH") "Look for the libdw library in this extra path"
    
    209 227
         ]
    
    210 228
       where
    
    211 229
         progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)]
    
    ... ... @@ -487,6 +505,9 @@ mkTarget opts = do
    487 505
         tgtSupportsIdentDirective <- checkIdentDirective cc
    
    488 506
         tgtSupportsGnuNonexecStack <- checkGnuNonexecStack archOs cc
    
    489 507
         tgtHasLibm <- checkTargetHasLibm cc
    
    508
    +    tgtRTSWithLibdw <- case optDwarfUnwind opts of
    
    509
    +      Just True -> checkTargetHasLibdw cc (optLibdwIncludes opts) (optLibdwLibraries opts)
    
    510
    +      _         -> pure Nothing
    
    490 511
     
    
    491 512
         -- code generator configuration
    
    492 513
         tgtUnregisterised <- determineUnregisterised archOs (optUnregisterised opts)
    
    ... ... @@ -528,6 +549,7 @@ mkTarget opts = do
    528 549
                        , tgtTablesNextToCode
    
    529 550
                        , tgtUseLibffiForAdjustors = tgtUseLibffi
    
    530 551
                        , tgtHasLibm
    
    552
    +                   , tgtRTSWithLibdw
    
    531 553
                        , tgtSymbolsHaveLeadingUnderscore
    
    532 554
                        , tgtSupportsSubsectionsViaSymbols
    
    533 555
                        , tgtSupportsIdentDirective
    

  • utils/ghc-toolchain/ghc-toolchain.cabal
    ... ... @@ -12,6 +12,7 @@ library
    12 12
         exposed-modules:
    
    13 13
                           GHC.Toolchain,
    
    14 14
                           GHC.Toolchain.Lens,
    
    15
    +                      GHC.Toolchain.Library,
    
    15 16
                           GHC.Toolchain.Monad,
    
    16 17
                           GHC.Toolchain.PlatformDetails,
    
    17 18
                           GHC.Toolchain.Prelude,
    

  • utils/ghc-toolchain/src/GHC/Toolchain/Library.hs
    1
    +module GHC.Toolchain.Library
    
    2
    +  ( Library(..)
    
    3
    +  )
    
    4
    +  where
    
    5
    +
    
    6
    +import System.FilePath
    
    7
    +import GHC.Toolchain.Prelude
    
    8
    +
    
    9
    +data Library = Library { libName :: String
    
    10
    +                       , includePath :: Maybe FilePath
    
    11
    +                       , libraryPath :: Maybe FilePath
    
    12
    +                       }
    
    13
    +    deriving (Read, Eq, Ord)
    
    14
    +
    
    15
    +instance Show Library where
    
    16
    +  -- Normalise filepaths before showing to aid with diffing the target files.
    
    17
    +  show (Library n i l) = unwords
    
    18
    +    [ "Library { libName = ", show n
    
    19
    +    , ", includePath = ", show (normalise <$> i)
    
    20
    +    , ", libraryPath =", show (normalise <$> l)
    
    21
    +    , "}"]
    
    22
    +

  • utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
    ... ... @@ -6,6 +6,7 @@ module GHC.Toolchain.PlatformDetails
    6 6
         , checkIdentDirective
    
    7 7
         , checkGnuNonexecStack
    
    8 8
         , checkTargetHasLibm
    
    9
    +    , checkTargetHasLibdw
    
    9 10
         ) where
    
    10 11
     
    
    11 12
     import Data.List (isInfixOf)
    
    ... ... @@ -17,6 +18,7 @@ import GHC.Toolchain.Prelude
    17 18
     import GHC.Toolchain.Utils
    
    18 19
     import GHC.Toolchain.Target
    
    19 20
     import GHC.Toolchain.Program
    
    21
    +import GHC.Toolchain.Library
    
    20 22
     import GHC.Toolchain.Tools.Cc
    
    21 23
     import GHC.Toolchain.Tools.Nm
    
    22 24
     
    
    ... ... @@ -156,25 +158,66 @@ checkGnuNonexecStack archOs =
    156 158
                        ]
    
    157 159
     
    
    158 160
     checkTargetHasLibm :: Cc -> M Bool
    
    159
    -checkTargetHasLibm cc0 = testCompile "whether target has libm" prog cc
    
    161
    +checkTargetHasLibm cc = testLib cc "m" "atan" Nothing
    
    162
    +
    
    163
    +checkTargetHasLibdw :: Cc -> Maybe FilePath -> Maybe FilePath -> M (Maybe Library)
    
    164
    +checkTargetHasLibdw cc mincludeDir mlibDir = do
    
    165
    +  b1 <- testHeader cc "elfutils/libdwfl.h" mincludeDir
    
    166
    +  b2 <- testLib cc "dw" "dwfl_attach_state" mlibDir
    
    167
    +  return $
    
    168
    +    if b1 && b2
    
    169
    +    then Just
    
    170
    +      Library{ libName = "dw"
    
    171
    +             , includePath = mincludeDir, libraryPath = mlibDir}
    
    172
    +    else Nothing
    
    173
    +
    
    174
    +
    
    175
    +--------------------------------------------------------------------------------
    
    176
    +-- Utilities
    
    177
    +--------------------------------------------------------------------------------
    
    178
    +
    
    179
    +asmStmt :: String -> String
    
    180
    +asmStmt s = "__asm__(\"" ++ foldMap escape s ++ "\");"
    
    160 181
       where
    
    161
    -    cc = cc0 & _ccProgram % _prgFlags %++ "-lm"
    
    182
    +    escape '"' = "\\\""
    
    183
    +    escape c   = [c]
    
    184
    +
    
    185
    +-- | Check whether a lib is found and can be linked against.
    
    186
    +-- Like @AC_CHECK_LIB@.
    
    187
    +testLib :: Cc
    
    188
    +        -> String         -- ^ Lib name
    
    189
    +        -> String         -- ^ Lib symbol
    
    190
    +        -> Maybe FilePath -- ^ Library dir (-L)
    
    191
    +        -> M Bool
    
    192
    +testLib cc0 libname symbol mlibDir = testCompile ("whether target has lib" ++ libname) prog cc2
    
    193
    +  where
    
    194
    +    cc1 = cc0 & _ccProgram % _prgFlags %++ ("-l" ++ libname)
    
    195
    +    cc2 | Just libDir <- mlibDir
    
    196
    +        = cc1 & _ccProgram % _prgFlags %++ ("-L" ++ libDir)
    
    197
    +        | otherwise = cc1
    
    162 198
         prog = unlines
    
    163
    -        [ "char atan (void);"
    
    199
    +        [ "char " ++ symbol ++ " (void);"
    
    164 200
             , "int"
    
    165 201
             , "main (void)"
    
    166 202
             , "{"
    
    167
    -        , "return atan ();"
    
    203
    +        , "return " ++ symbol ++ " ();"
    
    168 204
             , "  ;"
    
    169 205
             , "  return 0;"
    
    170 206
             , "}"
    
    171 207
             ]
    
    172 208
     
    
    173
    -asmStmt :: String -> String
    
    174
    -asmStmt s = "__asm__(\"" ++ foldMap escape s ++ "\");"
    
    209
    +-- | Like @AC_CHECK_HEADER@
    
    210
    +testHeader :: Cc
    
    211
    +           -> String         -- ^ Header to check for
    
    212
    +           -> Maybe FilePath -- ^ Extra path
    
    213
    +           -> M Bool
    
    214
    +testHeader cc0 header mincludeDir = testCompile ("whether target has <" ++ header ++ ">") prog cc1
    
    175 215
       where
    
    176
    -    escape '"' = "\\\""
    
    177
    -    escape c   = [c]
    
    216
    +    cc1 | Just includeDir <- mincludeDir
    
    217
    +        = cc0 & _ccProgram % _prgFlags %++ ("-I" ++ includeDir)
    
    218
    +        | otherwise = cc0
    
    219
    +    prog = unlines
    
    220
    +        [ "#include <" ++ header ++ ">" ]
    
    178 221
     
    
    179 222
     -- | Try compiling a program, returning 'True' if successful.
    
    180 223
     testCompile :: String -> String -> Cc -> M Bool
    

  • utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
    1 1
     {-# LANGUAGE RecordWildCards #-}
    
    2 2
     {-# LANGUAGE NamedFieldPuns #-}
    
    3
    +{-# LANGUAGE MultiWayIf #-}
    
    3 4
     module GHC.Toolchain.Target
    
    4 5
       (
    
    5 6
         -- * A Toolchain Target
    
    ... ... @@ -7,6 +8,9 @@ module GHC.Toolchain.Target
    7 8
     
    
    8 9
       , WordSize(..), wordSize2Bytes
    
    9 10
     
    
    11
    +    -- ** Queries
    
    12
    +  , tgtSupportsSMP, tgtRTSLinkerOnlySupportsSharedLibs
    
    13
    +
    
    10 14
         -- ** Lenses
    
    11 15
       , _tgtCC, _tgtCxx, _tgtCpp, _tgtHsCpp
    
    12 16
     
    
    ... ... @@ -19,6 +23,7 @@ import GHC.Platform.ArchOS
    19 23
     
    
    20 24
     import GHC.Toolchain.Prelude
    
    21 25
     import GHC.Toolchain.Program
    
    26
    +import GHC.Toolchain.Library
    
    22 27
     
    
    23 28
     import GHC.Toolchain.Tools.Cc
    
    24 29
     import GHC.Toolchain.Tools.Cxx
    
    ... ... @@ -56,11 +61,14 @@ data Target = Target
    56 61
         -- , tgtHasThreadedRts :: Bool -- We likely just need this when bootstrapping
    
    57 62
         , tgtUseLibffiForAdjustors :: Bool
    
    58 63
         -- ^ We need to know whether or not to include libffi headers, and generate additional code for it
    
    59
    -
    
    60
    -      -- Target support
    
    61 64
         , tgtHasLibm :: Bool
    
    62 65
         -- ^ Does this target have a libm library that should always be linked against?
    
    63 66
     
    
    67
    +    -- RTS capabilities
    
    68
    +    , tgtRTSWithLibdw :: Maybe Library
    
    69
    +    -- ^ Whether this target RTS is built with libdw support (for DWARF
    
    70
    +    -- unwinding), and if yes, the 'Library' configuration.
    
    71
    +
    
    64 72
           -- C toolchain
    
    65 73
         , tgtCCompiler :: Cc
    
    66 74
         , tgtCxxCompiler :: Cxx
    
    ... ... @@ -126,6 +134,7 @@ instance Show Target where
    126 134
         , ", tgtTablesNextToCode = " ++ show tgtTablesNextToCode
    
    127 135
         , ", tgtUseLibffiForAdjustors = " ++ show tgtUseLibffiForAdjustors
    
    128 136
         , ", tgtHasLibm = " ++ show tgtHasLibm
    
    137
    +    , ", tgtRTSWithLibdw = " ++ show tgtRTSWithLibdw
    
    129 138
         , ", tgtCCompiler = " ++ show tgtCCompiler
    
    130 139
         , ", tgtCxxCompiler = " ++ show tgtCxxCompiler
    
    131 140
         , ", tgtCPreprocessor = " ++ show tgtCPreprocessor
    
    ... ... @@ -146,6 +155,54 @@ instance Show Target where
    146 155
         , "}"
    
    147 156
         ]
    
    148 157
     
    
    158
    +--------------------------------------------------------------------------------
    
    159
    +-- Queries
    
    160
    +--------------------------------------------------------------------------------
    
    161
    +
    
    162
    +tgtSupportsSMP :: Target -> Bool
    
    163
    +tgtSupportsSMP Target{..} = do
    
    164
    +  let goodArch =
    
    165
    +        isARM (archOS_arch tgtArchOs)
    
    166
    +          || archOS_arch tgtArchOs `elem`
    
    167
    +              [ ArchX86
    
    168
    +              , ArchX86_64
    
    169
    +              , ArchPPC
    
    170
    +              , ArchPPC_64 ELF_V1
    
    171
    +              , ArchPPC_64 ELF_V2
    
    172
    +              , ArchAArch64
    
    173
    +              , ArchS390X
    
    174
    +              , ArchRISCV64
    
    175
    +              , ArchLoongArch64 ]
    
    176
    +
    
    177
    +  if   -- The THREADED_RTS requires `BaseReg` to be in a register and the
    
    178
    +       -- Unregisterised mode doesn't allow that.
    
    179
    +     | tgtUnregisterised    -> False
    
    180
    +       -- We don't support load/store barriers pre-ARMv7. See #10433.
    
    181
    +     | ArchARM ver _ _ <- archOS_arch tgtArchOs
    
    182
    +     , ver < ARMv7          -> False
    
    183
    +     | goodArch             -> True
    
    184
    +     | otherwise            -> False
    
    185
    +
    
    186
    +-- | Does the target RTS linker only support loading shared libraries?
    
    187
    +-- If true, this has several implications:
    
    188
    +-- 1. The GHC driver must not do loadArchive/loadObj etc and must
    
    189
    +--    always do loadDLL, regardless of whether host GHC is dynamic or
    
    190
    +--    not.
    
    191
    +-- 2. The GHC driver will always enable -dynamic-too when compiling
    
    192
    +--    vanilla way with TH codegen requirement.
    
    193
    +-- 3. ghci will always enforce dynamic ways even if -dynamic or
    
    194
    +--    -dynamic-too is not explicitly passed.
    
    195
    +-- 4. Cabal must not build ghci objects since it's not supported by
    
    196
    +--    the target.
    
    197
    +-- 5. The testsuite driver will use dyn way for TH/ghci tests even
    
    198
    +--    when host GHC is static.
    
    199
    +-- 6. TH/ghci doesn't work if stage1 is built without shared libraries
    
    200
    +--    (e.g. quickest/fully_static).
    
    201
    +tgtRTSLinkerOnlySupportsSharedLibs :: Target -> Bool
    
    202
    +tgtRTSLinkerOnlySupportsSharedLibs Target{tgtArchOs} =
    
    203
    +  archOS_arch tgtArchOs `elem`
    
    204
    +    [ ArchWasm32 ]
    
    205
    +
    
    149 206
     --------------------------------------------------------------------------------
    
    150 207
     -- Lenses
    
    151 208
     --------------------------------------------------------------------------------