
Cheng Shao pushed to branch wip/14554-wasm-fix at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: f2fbf0db by Rodrigo Mesquita at 2025-08-23T19:21:31+02:00 ghc-toolchain: Move UseLibdw to per-Target file To support DWARF unwinding, the RTS must be built with the -f+libdw flag and with the -DUSE_LIBDW macro definition. These flags are passed on build by Hadrian when --enable-dwarf-unwinding is specified at configure time. Whether the RTS was built with support for DWARF is a per-target property, and as such, it was moved to the per-target GHC.Toolchain.Target.Target file. Additionally, we keep in the target file the include and library paths for finding libdw, since libdw should be checked at configure time (be it by configure, or ghc-toolchain, that libdw is properly available). Preserving the user-given include paths for libdw facilitates in the future building the RTS on demand for a given target (if we didn't keep that user input, we couldn't) Towards #26227 - - - - - 18 changed files: - compiler/GHC/Driver/Session.hs - hadrian/bindist/Makefile - hadrian/bindist/config.mk.in - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/cfg/system.config.in - hadrian/src/Oracles/Flag.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings/Packages.hs - m4/fp_find_libdw.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/ghc-toolchain.cabal - + utils/ghc-toolchain/src/GHC/Toolchain/Library.hs - utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3509,7 +3509,8 @@ compilerInfo dflags ("LLVM llvm-as command", queryCmdMaybe id tgtLlvmAs), ("LLVM llvm-as flags", queryFlagsMaybe id tgtLlvmAs), ("Tables next to code", queryBool tgtTablesNextToCode), - ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore) + ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore), + ("RTS expects libdw", queryBool (isJust . tgtRTSWithLibdw)) ] ++ [("Project version", projectVersion dflags), ("Project Git commit id", cProjectGitCommitId), ===================================== hadrian/bindist/Makefile ===================================== @@ -90,7 +90,6 @@ lib/settings : config.mk @echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@ @echo ',("Support SMP", "$(GhcWithSMP)")' >> $@ @echo ',("RTS ways", "$(GhcRTSWays)")' >> $@ - @echo ',("RTS expects libdw", "$(GhcRtsWithLibdw)")' >> $@ @echo ',("Relative Global Package DB", "package.conf.d")' >> $@ @echo ',("base unit-id", "$(BaseUnitId)")' >> $@ @echo "]" >> $@ ===================================== hadrian/bindist/config.mk.in ===================================== @@ -172,7 +172,7 @@ UseLibffiForAdjustors=@UseLibffiForAdjustors@ # GHC needs arch-specific tweak at least in # rts/Libdw.c:set_initial_registers() -GhcRtsWithLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO)) +UseLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO)) #----------------------------------------------------------------------------- # Settings ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -13,6 +13,7 @@ Target , tgtTablesNextToCode = True , tgtUseLibffiForAdjustors = True , tgtHasLibm = True +, tgtRTSWithLibdw = Nothing , tgtCCompiler = Cc {ccProgram = Program {prgPath = "@CC_STAGE0@", prgFlags = @CONF_CC_OPTS_STAGE0List@}} , tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@CC_STAGE0@", prgFlags = @CONF_CXX_OPTS_STAGE0List@}} , tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@CPPCmd_STAGE0@", prgFlags = @CONF_CPP_OPTS_STAGE0List@}} ===================================== hadrian/cfg/default.target.in ===================================== @@ -13,6 +13,7 @@ Target , tgtTablesNextToCode = @TablesNextToCodeBool@ , tgtUseLibffiForAdjustors = @UseLibffiForAdjustorsBool@ , tgtHasLibm = @TargetHasLibmBool@ +, tgtRTSWithLibdw = @UseLibdwMaybeLibrary@ , tgtCCompiler = Cc {ccProgram = Program {prgPath = "@CC@", prgFlags = @CONF_CC_OPTS_STAGE2List@}} , tgtCxxCompiler = Cxx {cxxProgram = Program {prgPath = "@CXX@", prgFlags = @CONF_CXX_OPTS_STAGE2List@}} , tgtCPreprocessor = Cpp {cppProgram = Program {prgPath = "@CPPCmd@", prgFlags = @CONF_CPP_OPTS_STAGE2List@}} ===================================== hadrian/cfg/system.config.in ===================================== @@ -99,9 +99,6 @@ use-system-ffi = @UseSystemLibFFI@ ffi-include-dir = @FFIIncludeDir@ ffi-lib-dir = @FFILibDir@ -libdw-include-dir = @LibdwIncludeDir@ -libdw-lib-dir = @LibdwLibDir@ - libnuma-include-dir = @LibNumaIncludeDir@ libnuma-lib-dir = @LibNumaLibDir@ @@ -111,7 +108,6 @@ libzstd-lib-dir = @LibZstdLibDir@ # Optional Dependencies: #======================= -use-lib-dw = @UseLibdw@ use-lib-zstd = @UseLibZstd@ static-lib-zstd = @UseStaticLibZstd@ use-lib-numa = @UseLibNuma@ ===================================== hadrian/src/Oracles/Flag.hs ===================================== @@ -7,7 +7,7 @@ module Oracles.Flag ( targetRTSLinkerOnlySupportsSharedLibs, targetSupportsThreadedRts, targetSupportsSMP, - useLibffiForAdjustors, + useLibffiForAdjustors, useLibdw, arSupportsDashL, arSupportsAtFile ) where @@ -29,7 +29,6 @@ data Flag = CrossCompiling | UseSystemFfi | BootstrapThreadedRts | BootstrapEventLoggingRts - | UseLibdw | UseLibnuma | UseLibzstd | StaticLibzstd @@ -53,7 +52,6 @@ flag f = do UseSystemFfi -> "use-system-ffi" BootstrapThreadedRts -> "bootstrap-threaded-rts" BootstrapEventLoggingRts -> "bootstrap-event-logging-rts" - UseLibdw -> "use-lib-dw" UseLibnuma -> "use-lib-numa" UseLibzstd -> "use-lib-zstd" StaticLibzstd -> "static-lib-zstd" @@ -147,3 +145,6 @@ targetSupportsSMP = do useLibffiForAdjustors :: Action Bool useLibffiForAdjustors = queryTargetTarget tgtUseLibffiForAdjustors + +useLibdw :: Action Bool +useLibdw = queryTargetTarget (isJust . tgtRTSWithLibdw) ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -54,8 +54,6 @@ data Setting = CursesIncludeDir | GmpLibDir | IconvIncludeDir | IconvLibDir - | LibdwIncludeDir - | LibdwLibDir | LibnumaIncludeDir | LibnumaLibDir | LibZstdIncludeDir @@ -94,8 +92,6 @@ setting key = lookupSystemConfig $ case key of GmpLibDir -> "gmp-lib-dir" IconvIncludeDir -> "iconv-include-dir" IconvLibDir -> "iconv-lib-dir" - LibdwIncludeDir -> "libdw-include-dir" - LibdwLibDir -> "libdw-lib-dir" LibnumaIncludeDir -> "libnuma-include-dir" LibnumaLibDir -> "libnuma-lib-dir" LibZstdIncludeDir -> "libzstd-include-dir" ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -432,7 +432,7 @@ bindistRules = do , interpolateVar "TargetWordBigEndian" $ getTarget isBigEndian , interpolateVar "TargetWordSize" $ getTarget wordSize , interpolateVar "Unregisterised" $ yesNo <$> getTarget tgtUnregisterised - , interpolateVar "UseLibdw" $ fmap yesNo $ interp $ getFlag UseLibdw + , interpolateVar "UseLibdw" $ yesNo <$> getTarget (isJust . tgtRTSWithLibdw) , interpolateVar "UseLibffiForAdjustors" $ yesNo <$> getTarget tgtUseLibffiForAdjustors , interpolateVar "GhcWithSMP" $ yesNo <$> targetSupportsSMP , interpolateVar "BaseUnitId" $ pkgUnitId Stage1 base @@ -488,7 +488,6 @@ generateSettings settingsFile = do , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage)) , ("Support SMP", expr $ yesNo <$> targetSupportsSMP) , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays) - , ("RTS expects libdw", yesNo <$> getFlag UseLibdw) , ("Relative Global Package DB", pure rel_pkg_db) , ("base unit-id", pure base_unit_id) ] ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -8,6 +8,7 @@ import Packages import Settings import Settings.Builders.Common (wayCcArgs) +import qualified GHC.Toolchain.Library as Lib import GHC.Toolchain.Target import GHC.Platform.ArchOS import Data.Version.Extra @@ -305,8 +306,8 @@ rtsPackageArgs = package rts ? do useSystemFfi <- getFlag UseSystemFfi ffiIncludeDir <- getSetting FfiIncludeDir ffiLibraryDir <- getSetting FfiLibDir - libdwIncludeDir <- getSetting LibdwIncludeDir - libdwLibraryDir <- getSetting LibdwLibDir + libdwIncludeDir <- queryTarget (Lib.includePath <=< tgtRTSWithLibdw) + libdwLibraryDir <- queryTarget (Lib.libraryPath <=< tgtRTSWithLibdw) libnumaIncludeDir <- getSetting LibnumaIncludeDir libnumaLibraryDir <- getSetting LibnumaLibDir libzstdIncludeDir <- getSetting LibZstdIncludeDir @@ -444,7 +445,7 @@ rtsPackageArgs = package rts ? do , flag UseLibpthread `cabalFlag` "need-pthread" , flag UseLibbfd `cabalFlag` "libbfd" , flag NeedLibatomic `cabalFlag` "need-atomic" - , flag UseLibdw `cabalFlag` "libdw" + , useLibdw `cabalFlag` "libdw" , flag UseLibnuma `cabalFlag` "libnuma" , flag UseLibzstd `cabalFlag` "libzstd" , flag StaticLibzstd `cabalFlag` "static-libzstd" @@ -454,7 +455,7 @@ rtsPackageArgs = package rts ? do , Debug `wayUnit` way `cabalFlag` "find-ptr" ] , builder (Cabal Setup) ? mconcat - [ cabalExtraDirs libdwIncludeDir libdwLibraryDir + [ useLibdw ? cabalExtraDirs (fromMaybe "" libdwIncludeDir) (fromMaybe "" libdwLibraryDir) , cabalExtraDirs libnumaIncludeDir libnumaLibraryDir , cabalExtraDirs libzstdIncludeDir libzstdLibraryDir , useSystemFfi ? cabalExtraDirs ffiIncludeDir ffiLibraryDir @@ -468,7 +469,7 @@ rtsPackageArgs = package rts ? do , builder HsCpp ? pure [ "-DTOP=" ++ show top ] - , builder HsCpp ? flag UseLibdw ? arg "-DUSE_LIBDW" ] + , builder HsCpp ? useLibdw ? arg "-DUSE_LIBDW" ] -- Compile various performance-critical pieces *without* -fPIC -dynamic -- 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], AC_ARG_ENABLE(dwarf-unwind, [AS_HELP_STRING([--enable-dwarf-unwind], [Enable DWARF unwinding support in the runtime system via elfutils' libdw [default=no]])], - [], - [enable_dwarf_unwind=no]) + [FP_CAPITALIZE_YES_NO(["$enableval"], [enable_dwarf_unwind])], + [enable_dwarf_unwind=NO]) UseLibdw=NO - if test "$enable_dwarf_unwind" != "no" ; then + if test "$enable_dwarf_unwind" != "NO" ; then CFLAGS2="$CFLAGS" CFLAGS="$LIBDW_CFLAGS $CFLAGS" LDFLAGS2="$LDFLAGS" @@ -43,7 +43,7 @@ AC_DEFUN([FP_FIND_LIBDW], [AC_CHECK_LIB(dw, dwfl_attach_state, [UseLibdw=YES])]) - if test "x:$enable_dwarf_unwind:$UseLibdw" = "x:yes:NO" ; then + if test "x:$enable_dwarf_unwind:$UseLibdw" = "x:YES:NO" ; then AC_MSG_ERROR([Cannot find system libdw (required by --enable-dwarf-unwind)]) fi ===================================== m4/ghc_toolchain.m4 ===================================== @@ -120,6 +120,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], ENABLE_GHC_TOOLCHAIN_ARG([tables-next-to-code], [$TablesNextToCode]) ENABLE_GHC_TOOLCHAIN_ARG([ld-override], [$enable_ld_override]) ENABLE_GHC_TOOLCHAIN_ARG([libffi-adjustors], [$UseLibffiForAdjustors]) + ENABLE_GHC_TOOLCHAIN_ARG([dwarf-unwind], [$enable_dwarf_unwind]) dnl We store USER_* variants of all user-specified flags to pass them over to ghc-toolchain. ADD_GHC_TOOLCHAIN_ARG_CHOOSE([cc-opt], [$USER_CONF_CC_OPTS_STAGE2], [$USER_CFLAGS]) @@ -130,6 +131,8 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], ADD_GHC_TOOLCHAIN_ARG([hs-cpp-opt], [$USER_HS_CPP_ARGS]) ADD_GHC_TOOLCHAIN_ARG([js-cpp-opt], [$USER_JS_CPP_ARGS]) ADD_GHC_TOOLCHAIN_ARG([cmm-cpp-opt], [$USER_CMM_CPP_ARGS]) + ADD_GHC_TOOLCHAIN_ARG([libdw-includes], [$LibdwIncludeDir]) + ADD_GHC_TOOLCHAIN_ARG([libdw-libraries], [$LibdwLibDir]) INVOKE_GHC_TOOLCHAIN() ===================================== m4/prep_target_file.m4 ===================================== @@ -78,6 +78,22 @@ AC_DEFUN([PREP_MAYBE_PROGRAM],[ AC_SUBST([$1MaybeProg]) ]) +# PREP_MAYBE_LIBRARY +# ========================= +# +# Introduce a substitution [$1MaybeProg] with +# * Nothing, if $$1 is empty or "NO" +# * Just the library otherwise +AC_DEFUN([PREP_MAYBE_LIBRARY],[ + if test -z "$$1" || test "$$1" = "NO"; then + $1MaybeLibrary=Nothing + else + PREP_LIST([$2]) + $1MaybeLibrary="Just (Library { libName = \"$2\", includePath = \"$3\", libraryPath = \"$4\" })" + fi + AC_SUBST([$1MaybeLibrary]) +]) + # PREP_MAYBE_STRING # ========================= # @@ -180,6 +196,10 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([CONF_CXX_OPTS_STAGE2]) PREP_LIST([CONF_CC_OPTS_STAGE2]) + PREP_MAYBE_STRING([LibdwIncludeDir]) + PREP_MAYBE_STRING([LibdwLibDir]) + PREP_MAYBE_LIBRARY([UseLibdw], [dw], [$LibdwIncludeDirMaybeStr], [$LibdwLibDirMaybeStr]) + dnl Host target PREP_BOOLEAN([ArSupportsAtFile_STAGE0]) PREP_BOOLEAN([ArSupportsDashL_STAGE0]) @@ -189,7 +209,6 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_LIST([CONF_CXX_OPTS_STAGE0]) PREP_LIST([CONF_GCC_LINKER_OPTS_STAGE0]) - if test -z "$MergeObjsCmd"; then MergeObjsCmdMaybe=Nothing else ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -62,6 +62,12 @@ data Opts = Opts -- see #23857 and #22550 for the very unfortunate story. , optLd :: ProgOpt , optUnregisterised :: Maybe Bool + + -- dwarf unwinding + , optDwarfUnwind :: Maybe Bool + , optLibdwIncludes :: Maybe FilePath + , optLibdwLibraries :: Maybe FilePath + , optTablesNextToCode :: Maybe Bool , optUseLibFFIForAdjustors :: Maybe Bool , optLdOverride :: Maybe Bool @@ -112,6 +118,9 @@ emptyOpts = Opts , optOtool = po0 , optInstallNameTool = po0 , optUnregisterised = Nothing + , optDwarfUnwind = Nothing + , optLibdwIncludes = Nothing + , optLibdwLibraries = Nothing , optTablesNextToCode = Nothing , optUseLibFFIForAdjustors = Nothing , optLdOverride = Nothing @@ -157,13 +166,18 @@ _optOutput = Lens optOutput (\x o -> o {optOutput=x}) _optTargetPrefix :: Lens Opts (Maybe String) _optTargetPrefix = Lens optTargetPrefix (\x o -> o {optTargetPrefix=x}) -_optLocallyExecutable, _optUnregisterised, _optTablesNextToCode, _optUseLibFFIForAdjustors, _optLdOvveride :: Lens Opts (Maybe Bool) +_optLocallyExecutable, _optUnregisterised, _optTablesNextToCode, _optUseLibFFIForAdjustors, _optLdOvveride, _optDwarfUnwind :: Lens Opts (Maybe Bool) _optLocallyExecutable = Lens optLocallyExecutable (\x o -> o {optLocallyExecutable=x}) _optUnregisterised = Lens optUnregisterised (\x o -> o {optUnregisterised=x}) +_optDwarfUnwind = Lens optDwarfUnwind (\x o -> o {optDwarfUnwind=x}) _optTablesNextToCode = Lens optTablesNextToCode (\x o -> o {optTablesNextToCode=x}) _optUseLibFFIForAdjustors = Lens optUseLibFFIForAdjustors (\x o -> o {optUseLibFFIForAdjustors=x}) _optLdOvveride = Lens optLdOverride (\x o -> o {optLdOverride=x}) +_optLibdwIncludes, _optLibdwLibraries :: Lens Opts (Maybe FilePath) +_optLibdwIncludes = Lens optLibdwIncludes (\x o -> o {optLibdwIncludes=x}) +_optLibdwLibraries = Lens optLibdwLibraries (\x o -> o {optLibdwLibraries=x}) + _optVerbosity :: Lens Opts Int _optVerbosity = Lens optVerbosity (\x o -> o {optVerbosity=x}) @@ -185,6 +199,7 @@ options = , enableDisable "libffi-adjustors" "the use of libffi for adjustors, even on platforms which have support for more efficient, native adjustor implementations." _optUseLibFFIForAdjustors , enableDisable "ld-override" "override gcc's default linker" _optLdOvveride , enableDisable "locally-executable" "the use of a target prefix which will be added to all tool names when searching for toolchain components" _optLocallyExecutable + , enableDisable "dwarf-unwind" "Enable DWARF unwinding support in the runtime system via elfutils' libdw" _optDwarfUnwind ] ++ concat [ progOpts "cc" "C compiler" _optCc @@ -206,6 +221,9 @@ options = , progOpts "ld" "linker" _optLd , progOpts "otool" "otool utility" _optOtool , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool + ] ++ + [ Option [] ["libdw-includes"] (ReqArg (set _optLibdwIncludes . Just) "PATH") "Look for libdw headers in this extra path" + , Option [] ["libdw-libraries"] (ReqArg (set _optLibdwLibraries . Just) "PATH") "Look for the libdw library in this extra path" ] where progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)] @@ -487,6 +505,9 @@ mkTarget opts = do tgtSupportsIdentDirective <- checkIdentDirective cc tgtSupportsGnuNonexecStack <- checkGnuNonexecStack archOs cc tgtHasLibm <- checkTargetHasLibm cc + tgtRTSWithLibdw <- case optDwarfUnwind opts of + Just True -> checkTargetHasLibdw cc (optLibdwIncludes opts) (optLibdwLibraries opts) + _ -> pure Nothing -- code generator configuration tgtUnregisterised <- determineUnregisterised archOs (optUnregisterised opts) @@ -528,6 +549,7 @@ mkTarget opts = do , tgtTablesNextToCode , tgtUseLibffiForAdjustors = tgtUseLibffi , tgtHasLibm + , tgtRTSWithLibdw , tgtSymbolsHaveLeadingUnderscore , tgtSupportsSubsectionsViaSymbols , tgtSupportsIdentDirective ===================================== utils/ghc-toolchain/ghc-toolchain.cabal ===================================== @@ -12,6 +12,7 @@ library exposed-modules: GHC.Toolchain, GHC.Toolchain.Lens, + GHC.Toolchain.Library, GHC.Toolchain.Monad, GHC.Toolchain.PlatformDetails, GHC.Toolchain.Prelude, ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Library.hs ===================================== @@ -0,0 +1,22 @@ +module GHC.Toolchain.Library + ( Library(..) + ) + where + +import System.FilePath +import GHC.Toolchain.Prelude + +data Library = Library { libName :: String + , includePath :: Maybe FilePath + , libraryPath :: Maybe FilePath + } + deriving (Read, Eq, Ord) + +instance Show Library where + -- Normalise filepaths before showing to aid with diffing the target files. + show (Library n i l) = unwords + [ "Library { libName = ", show n + , ", includePath = ", show (normalise <$> i) + , ", libraryPath =", show (normalise <$> l) + , "}"] + ===================================== utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs ===================================== @@ -6,6 +6,7 @@ module GHC.Toolchain.PlatformDetails , checkIdentDirective , checkGnuNonexecStack , checkTargetHasLibm + , checkTargetHasLibdw ) where import Data.List (isInfixOf) @@ -17,6 +18,7 @@ import GHC.Toolchain.Prelude import GHC.Toolchain.Utils import GHC.Toolchain.Target import GHC.Toolchain.Program +import GHC.Toolchain.Library import GHC.Toolchain.Tools.Cc import GHC.Toolchain.Tools.Nm @@ -156,25 +158,66 @@ checkGnuNonexecStack archOs = ] checkTargetHasLibm :: Cc -> M Bool -checkTargetHasLibm cc0 = testCompile "whether target has libm" prog cc +checkTargetHasLibm cc = testLib cc "m" "atan" Nothing + +checkTargetHasLibdw :: Cc -> Maybe FilePath -> Maybe FilePath -> M (Maybe Library) +checkTargetHasLibdw cc mincludeDir mlibDir = do + b1 <- testHeader cc "elfutils/libdwfl.h" mincludeDir + b2 <- testLib cc "dw" "dwfl_attach_state" mlibDir + return $ + if b1 && b2 + then Just + Library{ libName = "dw" + , includePath = mincludeDir, libraryPath = mlibDir} + else Nothing + + +-------------------------------------------------------------------------------- +-- Utilities +-------------------------------------------------------------------------------- + +asmStmt :: String -> String +asmStmt s = "__asm__(\"" ++ foldMap escape s ++ "\");" where - cc = cc0 & _ccProgram % _prgFlags %++ "-lm" + escape '"' = "\\\"" + escape c = [c] + +-- | Check whether a lib is found and can be linked against. +-- Like @AC_CHECK_LIB@. +testLib :: Cc + -> String -- ^ Lib name + -> String -- ^ Lib symbol + -> Maybe FilePath -- ^ Library dir (-L) + -> M Bool +testLib cc0 libname symbol mlibDir = testCompile ("whether target has lib" ++ libname) prog cc2 + where + cc1 = cc0 & _ccProgram % _prgFlags %++ ("-l" ++ libname) + cc2 | Just libDir <- mlibDir + = cc1 & _ccProgram % _prgFlags %++ ("-L" ++ libDir) + | otherwise = cc1 prog = unlines - [ "char atan (void);" + [ "char " ++ symbol ++ " (void);" , "int" , "main (void)" , "{" - , "return atan ();" + , "return " ++ symbol ++ " ();" , " ;" , " return 0;" , "}" ] -asmStmt :: String -> String -asmStmt s = "__asm__(\"" ++ foldMap escape s ++ "\");" +-- | Like @AC_CHECK_HEADER@ +testHeader :: Cc + -> String -- ^ Header to check for + -> Maybe FilePath -- ^ Extra path + -> M Bool +testHeader cc0 header mincludeDir = testCompile ("whether target has <" ++ header ++ ">") prog cc1 where - escape '"' = "\\\"" - escape c = [c] + cc1 | Just includeDir <- mincludeDir + = cc0 & _ccProgram % _prgFlags %++ ("-I" ++ includeDir) + | otherwise = cc0 + prog = unlines + [ "#include <" ++ header ++ ">" ] -- | Try compiling a program, returning 'True' if successful. testCompile :: String -> String -> Cc -> M Bool ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -19,6 +19,7 @@ import GHC.Platform.ArchOS import GHC.Toolchain.Prelude import GHC.Toolchain.Program +import GHC.Toolchain.Library import GHC.Toolchain.Tools.Cc import GHC.Toolchain.Tools.Cxx @@ -56,11 +57,14 @@ data Target = Target -- , tgtHasThreadedRts :: Bool -- We likely just need this when bootstrapping , tgtUseLibffiForAdjustors :: Bool -- ^ We need to know whether or not to include libffi headers, and generate additional code for it - - -- Target support , tgtHasLibm :: Bool -- ^ Does this target have a libm library that should always be linked against? + -- RTS capabilities + , tgtRTSWithLibdw :: Maybe Library + -- ^ Whether this target RTS is built with libdw support (for DWARF + -- unwinding), and if yes, the 'Library' configuration. + -- C toolchain , tgtCCompiler :: Cc , tgtCxxCompiler :: Cxx @@ -126,6 +130,7 @@ instance Show Target where , ", tgtTablesNextToCode = " ++ show tgtTablesNextToCode , ", tgtUseLibffiForAdjustors = " ++ show tgtUseLibffiForAdjustors , ", tgtHasLibm = " ++ show tgtHasLibm + , ", tgtRTSWithLibdw = " ++ show tgtRTSWithLibdw , ", tgtCCompiler = " ++ show tgtCCompiler , ", tgtCxxCompiler = " ++ show tgtCxxCompiler , ", tgtCPreprocessor = " ++ show tgtCPreprocessor View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2fbf0db689239127c77aac5a50cca0c... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2fbf0db689239127c77aac5a50cca0c... You're receiving this email because of your account on gitlab.haskell.org.