Duncan Coutts pushed to branch wip/dcoutts/windows-rts-dll at Glasgow Haskell Compiler / GHC Commits: fd2954cd by Duncan Coutts at 2025-12-10T14:59:29+00:00 Add minimal dlltool support to ghc-toolchain We will need dlltool to build ghc itself dynamically on windows, and probably we will end up needing dlltool for ghc to build Haskell packages dynamically as well. The dlltool is a tool that can create dll import libraries from .def files. These .def files list the exported symbols of dlls. Its somewhat like gnu linker scripts, but more limited. - - - - - df3d4fab by Duncan Coutts at 2025-12-10T14:59:29+00:00 Add minimal dlltool support into ./configure Find dlltool, and hopefully support finding it within the bundled llvm toolchain on windows. - - - - - 0855b657 by Duncan Coutts at 2025-12-10T14:59:29+00:00 Update the default host and target files for dlltool support - - - - - 371dfa49 by Duncan Coutts at 2025-12-10T14:59:29+00:00 Add dlltool as a hadrian builder Optional except on windows. - - - - - 2818cd89 by Duncan Coutts at 2025-12-10T14:59:29+00:00 Update and generate libHSghc-internal.def from .def.in file The only symbol that the rts imports from the ghc-internal package now is init_ghc_hs_iface. So the rts only needs an import lib that defines that one symbol. Also, remove the libHSghc-prim.def because it is redundant. The rts no longer imports anything from ghc-prim. Keep libHSffi.def for now. We may yet need it once it is clear how libffi is going to be built/used for ghc. - - - - - d22ed63b by Duncan Coutts at 2025-12-10T14:59:29+00:00 Add rule to build libHSghc-internal.dll.a and link into the rts On windows only, with dynamic linking. This is needed because on windows, all symbols in dlls must be resolved. No dangling symbols allowed. References to external symbols must be explicit. We resolve this with an import library. We create an import library for ghc-internal, a .dll.a file. This is a static archive containing .o files that define the symbols we need, and crucially have ".idata" sections that specifies the symbols the dll imports and from where. Note that we do not install this libHSghc-internal.dll.a, and it does not need to list all the symbols exported by that package. We create a special purpose import lib and only use it when linking the rts dll, so it only has to list the symbols that the rts uses from ghc-internal (which is exactly one symbol: init_ghc_hs_iface). - - - - - 15 changed files: - configure.ac - hadrian/cfg/default.host.target.in - hadrian/cfg/default.target.in - hadrian/src/Builder.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Rules/Library.hs - hadrian/src/Rules/Rts.hs - m4/fp_setup_windows_toolchain.m4 - m4/ghc_toolchain.m4 - m4/prep_target_file.m4 - − rts/win32/libHSghc-internal.def - + rts/win32/libHSghc-internal.def.in - − rts/win32/libHSghc-prim.def - utils/ghc-toolchain/exe/Main.hs - utils/ghc-toolchain/src/GHC/Toolchain/Target.hs Changes: ===================================== configure.ac ===================================== @@ -320,13 +320,16 @@ else AC_CHECK_TOOL([RANLIB],[ranlib]) AC_CHECK_TOOL([OBJDUMP],[objdump]) AC_CHECK_TOOL([WindresCmd],[windres]) + AC_CHECK_TOOL([DlltoolCmd],[dlltool]) AC_CHECK_TOOL([Genlib],[genlib]) if test "$HostOS" = "mingw32"; then AC_CHECK_TARGET_TOOL([WindresCmd],[windres]) + AC_CHECK_TARGET_TOOL([DlltoolCmd],[dlltool]) AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump]) WindresCmd="$(cygpath -m $WindresCmd)" + DlltoolCmd="$(cygpath -m $DlltoolCmd)" if test "$Genlib" != ""; then GenlibCmd="$(cygpath -m $Genlib)" @@ -1042,6 +1045,7 @@ echo "\ otool : $OtoolCmd install_name_tool : $InstallNameToolCmd windres : $WindresCmd + dlltool : $DlltoolCmd genlib : $GenlibCmd Happy : $HappyCmd ($HappyVersion) Alex : $AlexCmd ($AlexVersion) ===================================== hadrian/cfg/default.host.target.in ===================================== @@ -44,6 +44,7 @@ Target , tgtOpt = Nothing , tgtLlvmAs = Nothing , tgtWindres = Nothing +, tgtDlltool = Nothing , tgtOtool = Nothing , tgtInstallNameTool = Nothing } ===================================== hadrian/cfg/default.target.in ===================================== @@ -44,6 +44,7 @@ Target , tgtOpt = @OptCmdMaybeProg@ , tgtLlvmAs = @LlvmAsCmdMaybeProg@ , tgtWindres = @WindresCmdMaybeProg@ +, tgtDlltool = @DlltoolCmdMaybeProg@ , tgtOtool = @OtoolCmdMaybeProg@ , tgtInstallNameTool = @InstallNameToolCmdMaybeProg@ } ===================================== hadrian/src/Builder.hs ===================================== @@ -17,7 +17,7 @@ import Development.Shake.Classes import Development.Shake.Command import Development.Shake.FilePath import GHC.Generics -import GHC.Platform.ArchOS (ArchOS(..), Arch(..)) +import GHC.Platform.ArchOS (ArchOS(..), Arch(..), OS(..)) import qualified Hadrian.Builder as H import Hadrian.Builder hiding (Builder) import Hadrian.Builder.Ar @@ -183,6 +183,7 @@ data Builder = Alex | Objdump | Python | Ranlib + | Dlltool | Testsuite TestMode | Sphinx SphinxMode | Tar TarMode @@ -418,6 +419,7 @@ isOptional target = \case Alex -> True -- Most ar implemententions no longer need ranlib, but some still do Ranlib -> not $ Toolchain.arNeedsRanlib (tgtAr target) + Dlltool -> archOS_OS (tgtArchOs target) /= OSMinGW32 JsCpp -> not $ (archOS_arch . tgtArchOs) target == ArchJavaScript -- ArchWasm32 too? _ -> False @@ -451,6 +453,7 @@ systemBuilderPath builder = case builder of Objdump -> fromKey "objdump" Python -> fromKey "python" Ranlib -> fromTargetTC "ranlib" (maybeProg Toolchain.ranlibProgram . tgtRanlib) + Dlltool -> fromTargetTC "dlltool" (maybeProg id . tgtDlltool) Testsuite _ -> fromKey "python" Sphinx _ -> fromKey "sphinx-build" Tar _ -> fromKey "tar" ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -382,6 +382,7 @@ templateRules = do , interpolateSetting "ProjectPatchLevel1" ProjectPatchLevel1 , interpolateSetting "ProjectPatchLevel2" ProjectPatchLevel2 ] + templateRule "rts/win32/libHSghc-internal.def" projectVersion templateRule "docs/index.html" $ packageUnitIds Stage1 templateRule "docs/users_guide/ghc_config.py" $ mconcat [ projectVersion ===================================== hadrian/src/Rules/Library.hs ===================================== @@ -4,6 +4,8 @@ import Hadrian.BuildPath import Hadrian.Haskell.Cabal import Hadrian.Haskell.Cabal.Type import qualified Text.Parsec as Parsec +import GHC.Platform.ArchOS (ArchOS(archOS_OS), OS(..)) +import GHC.Toolchain.Target (Target(tgtArchOs)) import Base import Context @@ -205,9 +207,13 @@ jsObjects context = do srcs <- interpretInContext context (getContextData jsSrcs) mapM (objectPath context) srcs --- | Return extra object files needed to build the given library context. The --- resulting list is currently non-empty only when the package from the --- 'Context' is @ghc-internal@ built with in-tree GMP backend. +-- | Return extra object files needed to build the given library context. +-- +-- This is non-empty for: +-- +-- * @ghc-internal@ when built with in-tree GMP backend +-- * @rts@ on windows when linking dynamically +-- extraObjects :: Context -> Action [FilePath] extraObjects context | package context == ghcInternal = do @@ -215,6 +221,12 @@ extraObjects context "gmp" -> gmpObjects (stage context) _ -> return [] + | package context == rts = do + target <- interpretInContext context getStagedTarget + builddir <- buildPath context + return [ builddir -/- "libHSghc-internal.dll.a" + | archOS_OS (tgtArchOs target) == OSMinGW32 + , Dynamic `wayUnit` way context ] | otherwise = return [] -- | Return all the object files to be put into the library we're building for ===================================== hadrian/src/Rules/Rts.hs ===================================== @@ -43,6 +43,10 @@ rtsRules = priority 3 $ do buildPath -/- "libffi*.so*" %> copyLibffiDynamicUnix stage ".so" buildPath -/- "libffi*.dll*" %> copyLibffiDynamicWin stage + -- Not libffi: an import lib for the ghc-internal dll, to be linked + -- into the rts dll (windows only). + buildPath -/- "libHSghc-internal.dll.a" %> buildGhcInternalImportLib + withLibffi :: Stage -> (FilePath -> FilePath -> Action a) -> Action a withLibffi stage action = needLibffi stage >> (join $ action <$> libffiBuildPath stage @@ -154,6 +158,17 @@ needRtsLibffiTargets stage = do mapM (rtsLibffiLibrary stage) (Set.toList ways) return $ concat [ headers, dynLibffis, libffis_libs ] + +-- Solve the recursive dependency between rts and ghc-internal on +-- windows by creating an import lib for the ghc-internal dll, to be +-- linked into the rts dll. +buildGhcInternalImportLib :: FilePath -> Action () +buildGhcInternalImportLib target = do + let input = "rts/win32/libHSghc-internal.def" + output = target -- the .dll.a import lib + need [input] + runBuilder Dlltool ["-d", input, "-l", output] [input] [output] + -- Need symlinks generated by rtsRules. needRtsSymLinks :: Stage -> Set.Set Way -> Action () needRtsSymLinks stage rtsWays ===================================== m4/fp_setup_windows_toolchain.m4 ===================================== @@ -131,8 +131,8 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[ AR="${mingwbin}llvm-ar.exe" RANLIB="${mingwbin}llvm-ranlib.exe" OBJDUMP="${mingwbin}llvm-objdump.exe" - DLLTOOL="${mingwbin}llvm-dlltool.exe" WindresCmd="${mingwbin}llvm-windres.exe" + DlltoolCmd="${mingwbin}llvm-dlltool.exe" LLC="${mingwbin}llc.exe" OPT="${mingwbin}opt.exe" LLVMAS="${mingwbin}clang.exe" ===================================== m4/ghc_toolchain.m4 ===================================== @@ -95,6 +95,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN], echo "--merge-objs=$MergeObjsCmd" >> acargs echo "--readelf=$READELF" >> acargs echo "--windres=$WindresCmd" >> acargs + echo "--dlltool=$DlltoolCmd" >> acargs echo "--llc=$LlcCmd" >> acargs echo "--opt=$OptCmd" >> acargs echo "--llvm-as=$LlvmAsCmd" >> acargs ===================================== m4/prep_target_file.m4 ===================================== @@ -190,6 +190,7 @@ AC_DEFUN([PREP_TARGET_FILE],[ PREP_MAYBE_SIMPLE_PROGRAM([OptCmd]) PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags]) PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd]) + PREP_MAYBE_SIMPLE_PROGRAM([DlltoolCmd]) PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd]) PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd]) PREP_MAYBE_STRING([TargetVendor_CPP]) ===================================== rts/win32/libHSghc-internal.def deleted ===================================== @@ -1,49 +0,0 @@ - -LIBRARY "libHSghc-internal-@LibVersion@-ghc@ProjectVersion@.dll" - -EXPORTS - ghczminternal_GHCziInternalziInt_I8zh_con_info - ghczminternal_GHCziInternalziInt_I16zh_con_info - ghczminternal_GHCziInternalziInt_I32zh_con_info - ghczminternal_GHCziInternalziInt_I64zh_con_info - - ghczminternal_GHCziInternalziWord_W8zh_con_info - ghczminternal_GHCziInternalziWord_W16zh_con_info - ghczminternal_GHCziInternalziWord_W32zh_con_info - ghczminternal_GHCziInternalziWord_W64zh_con_info - - ghczminternal_GHCziInternalziStable_StablePtr_con_info - - ghczminternal_GHCziInternalziPack_unpackCString_closure - - ghczminternal_GHCziInternalziTopHandler_runIO_closure - ghczminternal_GHCziInternalziTopHandler_runNonIO_closure - - ghczminternal_GHCziInternalziIOziException_stackOverflow_closure - ghczminternal_GHCziInternalziIOziException_heapOverflow_closure - - ghczminternal_GHCziInternalziPtr_Ptr_con_info - ghczminternal_GHCziInternalziPtr_FunPtr_con_info - - ghczminternal_GHCziInternalziConcziIO_ensureIOManagerIsRunning_closure - ghczminternal_GHCziInternalziConcziIO_interruptIOManager_closure - ghczminternal_GHCziInternalziConcziIO_ioManagerCapabilitiesChanged_closure - ghczminternal_GHCziInternalziConcziSync_runSparks_closure - ghczminternal_GHCziInternalziEventziWindows_processRemoteCompletion_closure - - ghczminternal_GHCziInternalziTopHandler_flushStdHandles_closure - - ghczminternal_GHCziInternalziWeakziFinalizze_runFinalizzerBatch_closure - ghczminternal_GHCziInternalziPack_unpackCString_closure - ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnMVar_closure - ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnSTM_closure - ghczminternal_GHCziInternalziIOziException_allocationLimitExceeded_closure - ghczminternal_GHCziInternalziIOziException_stackOverflow_closure - ghczminternal_GHCziInternalziIOziException_cannotCompactFunction_closure - ghczminternal_GHCziInternalziIOziException_cannotCompactPinned_closure - ghczminternal_GHCziInternalziIOziException_cannotCompactMutable_closure - ghczminternal_GHCziInternalziControlziExceptionziBase_nonTermination_closure - ghczminternal_GHCziInternalziControlziExceptionziBase_nestedAtomically_closure - ghczminternal_GHCziInternalziExceptionziType_divZZeroException_closure - ghczminternal_GHCziInternalziExceptionziType_underflowException_closure - ghczminternal_GHCziInternalziExceptionziType_overflowException_closure ===================================== rts/win32/libHSghc-internal.def.in ===================================== @@ -0,0 +1,4 @@ +LIBRARY libHSghc-internal-@ProjectVersionForLib@.0-ghc@ProjectVersion@.dll + +EXPORTS + init_ghc_hs_iface ===================================== rts/win32/libHSghc-prim.def deleted ===================================== @@ -1,14 +0,0 @@ - -LIBRARY "libHSghc-internal-@LibVersion@-ghc@ProjectVersion@.dll" - -EXPORTS - - ghczminternal_GHCziInternalziTypes_True_closure - ghczminternal_GHCziInternalziTypes_False_closure - ghczminternal_GHCziInternalziTypes_Czh_con_info - ghczminternal_GHCziInternalziTypes_Izh_con_info - ghczminternal_GHCziInternalziTypes_Fzh_con_info - ghczminternal_GHCziInternalziTypes_Dzh_con_info - ghczminternal_GHCziInternalziTypes_Wzh_con_info - ghczminternal_GHCziInternalziTypes_Czh_static_info - ghczminternal_GHCziInternalziTypes_Izh_static_info ===================================== utils/ghc-toolchain/exe/Main.hs ===================================== @@ -56,6 +56,7 @@ data Opts = Opts , optOpt :: ProgOpt , optLlvmAs :: ProgOpt , optWindres :: ProgOpt + , optDlltool :: ProgOpt , optOtool :: ProgOpt , optInstallNameTool :: ProgOpt -- Note we don't actually configure LD into anything but @@ -114,6 +115,7 @@ emptyOpts = Opts , optOpt = po0 , optLlvmAs = po0 , optWindres = po0 + , optDlltool = po0 , optLd = po0 , optOtool = po0 , optInstallNameTool = po0 @@ -132,7 +134,7 @@ emptyOpts = Opts _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr, _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs, - _optWindres, _optLd, _optOtool, _optInstallNameTool + _optWindres, _optDlltool, _optLd, _optOtool, _optInstallNameTool :: Lens Opts ProgOpt _optCc = Lens optCc (\x o -> o {optCc=x}) _optCxx = Lens optCxx (\x o -> o {optCxx=x}) @@ -150,6 +152,7 @@ _optLlc = Lens optLlc (\x o -> o {optLlc=x}) _optOpt = Lens optOpt (\x o -> o {optOpt=x}) _optLlvmAs = Lens optLlvmAs (\x o -> o {optLlvmAs=x}) _optWindres = Lens optWindres (\x o -> o {optWindres=x}) +_optDlltool = Lens optDlltool (\x o -> o {optDlltool=x}) _optLd = Lens optLd (\x o -> o {optLd=x}) _optOtool = Lens optOtool (\x o -> o {optOtool=x}) _optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x}) @@ -218,6 +221,7 @@ options = , progOpts "opt" "LLVM opt utility" _optOpt , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs , progOpts "windres" "windres utility" _optWindres + , progOpts "dlltool" "Windows dll utility" _optDlltool , progOpts "ld" "linker" _optLd , progOpts "otool" "otool utility" _optOtool , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool @@ -481,12 +485,13 @@ mkTarget opts = do llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"] -- Windows-specific utilities - windres <- + (windres, dlltool) <- case archOS_OS archOs of OSMinGW32 -> do - windres <- findProgram "windres" (optWindres opts) ["windres"] - return (Just windres) - _ -> return Nothing + windres <- findProgram "windres" (optWindres opts) ["windres", "llvm-windres"] + dlltool <- findProgram "dlltool" (optDlltool opts) ["dlltool", "llvm-dlltool"] + return (Just windres, Just dlltool) + _ -> return (Nothing, Nothing) -- Darwin-specific utilities (otool, installNameTool) <- @@ -541,6 +546,7 @@ mkTarget opts = do , tgtOpt = opt , tgtLlvmAs = llvmAs , tgtWindres = windres + , tgtDlltool = dlltool , tgtOtool = otool , tgtInstallNameTool = installNameTool , tgtWordSize ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Target.hs ===================================== @@ -93,6 +93,7 @@ data Target = Target -- Windows-specific tools , tgtWindres :: Maybe Program + , tgtDlltool :: Maybe Program -- Darwin-specific tools , tgtOtool :: Maybe Program @@ -150,6 +151,7 @@ instance Show Target where , ", tgtOpt = " ++ show tgtOpt , ", tgtLlvmAs = " ++ show tgtLlvmAs , ", tgtWindres = " ++ show tgtWindres + , ", tgtDlltool = " ++ show tgtDlltool , ", tgtOtool = " ++ show tgtOtool , ", tgtInstallNameTool = " ++ show tgtInstallNameTool , "}" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da41a1a5a5771e410fc423808a5857b... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da41a1a5a5771e410fc423808a5857b... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Duncan Coutts (@dcoutts)