Duncan Coutts pushed to branch wip/dcoutts/windows-rts-dll at Glasgow Haskell Compiler / GHC

Commits:

15 changed files:

Changes:

  • configure.ac
    ... ... @@ -320,13 +320,16 @@ else
    320 320
         AC_CHECK_TOOL([RANLIB],[ranlib])
    
    321 321
         AC_CHECK_TOOL([OBJDUMP],[objdump])
    
    322 322
         AC_CHECK_TOOL([WindresCmd],[windres])
    
    323
    +    AC_CHECK_TOOL([DlltoolCmd],[dlltool])
    
    323 324
         AC_CHECK_TOOL([Genlib],[genlib])
    
    324 325
     
    
    325 326
         if test "$HostOS" = "mingw32"; then
    
    326 327
             AC_CHECK_TARGET_TOOL([WindresCmd],[windres])
    
    328
    +        AC_CHECK_TARGET_TOOL([DlltoolCmd],[dlltool])
    
    327 329
             AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump])
    
    328 330
     
    
    329 331
             WindresCmd="$(cygpath -m $WindresCmd)"
    
    332
    +	DlltoolCmd="$(cygpath -m $DlltoolCmd)"
    
    330 333
     
    
    331 334
             if test "$Genlib" != ""; then
    
    332 335
                 GenlibCmd="$(cygpath -m $Genlib)"
    
    ... ... @@ -1042,6 +1045,7 @@ echo "\
    1042 1045
        otool        : $OtoolCmd
    
    1043 1046
        install_name_tool : $InstallNameToolCmd
    
    1044 1047
        windres      : $WindresCmd
    
    1048
    +   dlltool      : $DlltoolCmd
    
    1045 1049
        genlib       : $GenlibCmd
    
    1046 1050
        Happy        : $HappyCmd ($HappyVersion)
    
    1047 1051
        Alex         : $AlexCmd ($AlexVersion)
    

  • hadrian/cfg/default.host.target.in
    ... ... @@ -44,6 +44,7 @@ Target
    44 44
     , tgtOpt = Nothing
    
    45 45
     , tgtLlvmAs = Nothing
    
    46 46
     , tgtWindres = Nothing
    
    47
    +, tgtDlltool = Nothing
    
    47 48
     , tgtOtool = Nothing
    
    48 49
     , tgtInstallNameTool = Nothing
    
    49 50
     }

  • hadrian/cfg/default.target.in
    ... ... @@ -44,6 +44,7 @@ Target
    44 44
     , tgtOpt = @OptCmdMaybeProg@
    
    45 45
     , tgtLlvmAs = @LlvmAsCmdMaybeProg@
    
    46 46
     , tgtWindres = @WindresCmdMaybeProg@
    
    47
    +, tgtDlltool = @DlltoolCmdMaybeProg@
    
    47 48
     , tgtOtool = @OtoolCmdMaybeProg@
    
    48 49
     , tgtInstallNameTool = @InstallNameToolCmdMaybeProg@
    
    49 50
     }

  • hadrian/src/Builder.hs
    ... ... @@ -17,7 +17,7 @@ import Development.Shake.Classes
    17 17
     import Development.Shake.Command
    
    18 18
     import Development.Shake.FilePath
    
    19 19
     import GHC.Generics
    
    20
    -import GHC.Platform.ArchOS (ArchOS(..), Arch(..))
    
    20
    +import GHC.Platform.ArchOS (ArchOS(..), Arch(..), OS(..))
    
    21 21
     import qualified Hadrian.Builder as H
    
    22 22
     import Hadrian.Builder hiding (Builder)
    
    23 23
     import Hadrian.Builder.Ar
    
    ... ... @@ -183,6 +183,7 @@ data Builder = Alex
    183 183
                  | Objdump
    
    184 184
                  | Python
    
    185 185
                  | Ranlib
    
    186
    +             | Dlltool
    
    186 187
                  | Testsuite TestMode
    
    187 188
                  | Sphinx SphinxMode
    
    188 189
                  | Tar TarMode
    
    ... ... @@ -418,6 +419,7 @@ isOptional target = \case
    418 419
         Alex     -> True
    
    419 420
         -- Most ar implemententions no longer need ranlib, but some still do
    
    420 421
         Ranlib   -> not $ Toolchain.arNeedsRanlib (tgtAr target)
    
    422
    +    Dlltool  -> archOS_OS (tgtArchOs target) /= OSMinGW32
    
    421 423
         JsCpp    -> not $ (archOS_arch . tgtArchOs) target == ArchJavaScript -- ArchWasm32 too?
    
    422 424
         _        -> False
    
    423 425
     
    
    ... ... @@ -451,6 +453,7 @@ systemBuilderPath builder = case builder of
    451 453
         Objdump         -> fromKey "objdump"
    
    452 454
         Python          -> fromKey "python"
    
    453 455
         Ranlib          -> fromTargetTC "ranlib" (maybeProg Toolchain.ranlibProgram . tgtRanlib)
    
    456
    +    Dlltool         -> fromTargetTC "dlltool" (maybeProg id . tgtDlltool)
    
    454 457
         Testsuite _     -> fromKey "python"
    
    455 458
         Sphinx _        -> fromKey "sphinx-build"
    
    456 459
         Tar _           -> fromKey "tar"
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -382,6 +382,7 @@ templateRules = do
    382 382
         , interpolateSetting "ProjectPatchLevel1" ProjectPatchLevel1
    
    383 383
         , interpolateSetting "ProjectPatchLevel2" ProjectPatchLevel2
    
    384 384
         ]
    
    385
    +  templateRule "rts/win32/libHSghc-internal.def" projectVersion
    
    385 386
       templateRule "docs/index.html" $ packageUnitIds Stage1
    
    386 387
       templateRule "docs/users_guide/ghc_config.py" $ mconcat
    
    387 388
         [ projectVersion
    

  • hadrian/src/Rules/Library.hs
    ... ... @@ -4,6 +4,8 @@ import Hadrian.BuildPath
    4 4
     import Hadrian.Haskell.Cabal
    
    5 5
     import Hadrian.Haskell.Cabal.Type
    
    6 6
     import qualified Text.Parsec      as Parsec
    
    7
    +import GHC.Platform.ArchOS (ArchOS(archOS_OS), OS(..))
    
    8
    +import GHC.Toolchain.Target (Target(tgtArchOs))
    
    7 9
     
    
    8 10
     import Base
    
    9 11
     import Context
    
    ... ... @@ -205,9 +207,13 @@ jsObjects context = do
    205 207
       srcs <- interpretInContext context (getContextData jsSrcs)
    
    206 208
       mapM (objectPath context) srcs
    
    207 209
     
    
    208
    --- | Return extra object files needed to build the given library context. The
    
    209
    --- resulting list is currently non-empty only when the package from the
    
    210
    --- 'Context' is @ghc-internal@ built with in-tree GMP backend.
    
    210
    +-- | Return extra object files needed to build the given library context.
    
    211
    +--
    
    212
    +-- This is non-empty for:
    
    213
    +--
    
    214
    +-- * @ghc-internal@ when built with in-tree GMP backend
    
    215
    +-- * @rts@ on windows when linking dynamically
    
    216
    +--
    
    211 217
     extraObjects :: Context -> Action [FilePath]
    
    212 218
     extraObjects context
    
    213 219
         | package context == ghcInternal = do
    
    ... ... @@ -215,6 +221,12 @@ extraObjects context
    215 221
                 "gmp" -> gmpObjects (stage context)
    
    216 222
                 _     -> return []
    
    217 223
     
    
    224
    +    | package context == rts = do
    
    225
    +          target   <- interpretInContext context getStagedTarget
    
    226
    +          builddir <- buildPath context
    
    227
    +          return [ builddir -/- "libHSghc-internal.dll.a"
    
    228
    +                 | archOS_OS (tgtArchOs target) == OSMinGW32
    
    229
    +                 , Dynamic `wayUnit` way context ]
    
    218 230
         | otherwise = return []
    
    219 231
     
    
    220 232
     -- | 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
    43 43
             buildPath -/- "libffi*.so*"    %> copyLibffiDynamicUnix stage ".so"
    
    44 44
             buildPath -/- "libffi*.dll*"   %> copyLibffiDynamicWin  stage
    
    45 45
     
    
    46
    +        -- Not libffi: an import lib for the ghc-internal dll, to be linked
    
    47
    +        -- into the rts dll (windows only).
    
    48
    +        buildPath -/- "libHSghc-internal.dll.a" %> buildGhcInternalImportLib
    
    49
    +
    
    46 50
     withLibffi :: Stage -> (FilePath -> FilePath -> Action a) -> Action a
    
    47 51
     withLibffi stage action = needLibffi stage
    
    48 52
                             >> (join $ action <$> libffiBuildPath stage
    
    ... ... @@ -154,6 +158,17 @@ needRtsLibffiTargets stage = do
    154 158
                 mapM (rtsLibffiLibrary stage) (Set.toList ways)
    
    155 159
             return $ concat [ headers, dynLibffis, libffis_libs ]
    
    156 160
     
    
    161
    +
    
    162
    +-- Solve the recursive dependency between rts and ghc-internal on
    
    163
    +-- windows by creating an import lib for the ghc-internal dll, to be
    
    164
    +-- linked into the rts dll.
    
    165
    +buildGhcInternalImportLib :: FilePath -> Action ()
    
    166
    +buildGhcInternalImportLib target = do
    
    167
    +    let input  = "rts/win32/libHSghc-internal.def"
    
    168
    +        output = target -- the .dll.a import lib
    
    169
    +    need [input]
    
    170
    +    runBuilder Dlltool ["-d", input, "-l", output] [input] [output]
    
    171
    +
    
    157 172
     -- Need symlinks generated by rtsRules.
    
    158 173
     needRtsSymLinks :: Stage -> Set.Set Way -> Action ()
    
    159 174
     needRtsSymLinks stage rtsWays
    

  • m4/fp_setup_windows_toolchain.m4
    ... ... @@ -131,8 +131,8 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
    131 131
         AR="${mingwbin}llvm-ar.exe"
    
    132 132
         RANLIB="${mingwbin}llvm-ranlib.exe"
    
    133 133
         OBJDUMP="${mingwbin}llvm-objdump.exe"
    
    134
    -    DLLTOOL="${mingwbin}llvm-dlltool.exe"
    
    135 134
         WindresCmd="${mingwbin}llvm-windres.exe"
    
    135
    +    DlltoolCmd="${mingwbin}llvm-dlltool.exe"
    
    136 136
         LLC="${mingwbin}llc.exe"
    
    137 137
         OPT="${mingwbin}opt.exe"
    
    138 138
         LLVMAS="${mingwbin}clang.exe"
    

  • m4/ghc_toolchain.m4
    ... ... @@ -95,6 +95,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
    95 95
         echo "--merge-objs=$MergeObjsCmd" >> acargs
    
    96 96
         echo "--readelf=$READELF" >> acargs
    
    97 97
         echo "--windres=$WindresCmd" >> acargs
    
    98
    +    echo "--dlltool=$DlltoolCmd" >> acargs
    
    98 99
         echo "--llc=$LlcCmd" >> acargs
    
    99 100
         echo "--opt=$OptCmd" >> acargs
    
    100 101
         echo "--llvm-as=$LlvmAsCmd" >> acargs
    

  • m4/prep_target_file.m4
    ... ... @@ -190,6 +190,7 @@ AC_DEFUN([PREP_TARGET_FILE],[
    190 190
         PREP_MAYBE_SIMPLE_PROGRAM([OptCmd])
    
    191 191
         PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags])
    
    192 192
         PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd])
    
    193
    +    PREP_MAYBE_SIMPLE_PROGRAM([DlltoolCmd])
    
    193 194
         PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd])
    
    194 195
         PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd])
    
    195 196
         PREP_MAYBE_STRING([TargetVendor_CPP])
    

  • rts/win32/libHSghc-internal.def deleted
    1
    -
    
    2
    -LIBRARY "libHSghc-internal-@LibVersion@-ghc@ProjectVersion@.dll"
    
    3
    -
    
    4
    -EXPORTS
    
    5
    -    ghczminternal_GHCziInternalziInt_I8zh_con_info
    
    6
    -    ghczminternal_GHCziInternalziInt_I16zh_con_info
    
    7
    -    ghczminternal_GHCziInternalziInt_I32zh_con_info
    
    8
    -    ghczminternal_GHCziInternalziInt_I64zh_con_info
    
    9
    -
    
    10
    -    ghczminternal_GHCziInternalziWord_W8zh_con_info
    
    11
    -    ghczminternal_GHCziInternalziWord_W16zh_con_info
    
    12
    -    ghczminternal_GHCziInternalziWord_W32zh_con_info
    
    13
    -    ghczminternal_GHCziInternalziWord_W64zh_con_info
    
    14
    -
    
    15
    -    ghczminternal_GHCziInternalziStable_StablePtr_con_info
    
    16
    -
    
    17
    -    ghczminternal_GHCziInternalziPack_unpackCString_closure
    
    18
    -
    
    19
    -    ghczminternal_GHCziInternalziTopHandler_runIO_closure
    
    20
    -    ghczminternal_GHCziInternalziTopHandler_runNonIO_closure
    
    21
    -
    
    22
    -    ghczminternal_GHCziInternalziIOziException_stackOverflow_closure
    
    23
    -    ghczminternal_GHCziInternalziIOziException_heapOverflow_closure
    
    24
    -
    
    25
    -    ghczminternal_GHCziInternalziPtr_Ptr_con_info
    
    26
    -    ghczminternal_GHCziInternalziPtr_FunPtr_con_info
    
    27
    -
    
    28
    -    ghczminternal_GHCziInternalziConcziIO_ensureIOManagerIsRunning_closure
    
    29
    -    ghczminternal_GHCziInternalziConcziIO_interruptIOManager_closure
    
    30
    -    ghczminternal_GHCziInternalziConcziIO_ioManagerCapabilitiesChanged_closure
    
    31
    -    ghczminternal_GHCziInternalziConcziSync_runSparks_closure
    
    32
    -    ghczminternal_GHCziInternalziEventziWindows_processRemoteCompletion_closure
    
    33
    -
    
    34
    -    ghczminternal_GHCziInternalziTopHandler_flushStdHandles_closure
    
    35
    -
    
    36
    -    ghczminternal_GHCziInternalziWeakziFinalizze_runFinalizzerBatch_closure
    
    37
    -    ghczminternal_GHCziInternalziPack_unpackCString_closure
    
    38
    -    ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnMVar_closure
    
    39
    -    ghczminternal_GHCziInternalziIOziException_blockedIndefinitelyOnSTM_closure
    
    40
    -    ghczminternal_GHCziInternalziIOziException_allocationLimitExceeded_closure
    
    41
    -    ghczminternal_GHCziInternalziIOziException_stackOverflow_closure
    
    42
    -    ghczminternal_GHCziInternalziIOziException_cannotCompactFunction_closure
    
    43
    -    ghczminternal_GHCziInternalziIOziException_cannotCompactPinned_closure
    
    44
    -    ghczminternal_GHCziInternalziIOziException_cannotCompactMutable_closure
    
    45
    -    ghczminternal_GHCziInternalziControlziExceptionziBase_nonTermination_closure
    
    46
    -    ghczminternal_GHCziInternalziControlziExceptionziBase_nestedAtomically_closure
    
    47
    -    ghczminternal_GHCziInternalziExceptionziType_divZZeroException_closure
    
    48
    -    ghczminternal_GHCziInternalziExceptionziType_underflowException_closure
    
    49
    -    ghczminternal_GHCziInternalziExceptionziType_overflowException_closure

  • rts/win32/libHSghc-internal.def.in
    1
    +LIBRARY libHSghc-internal-@ProjectVersionForLib@.0-ghc@ProjectVersion@.dll
    
    2
    +
    
    3
    +EXPORTS
    
    4
    +    init_ghc_hs_iface

  • rts/win32/libHSghc-prim.def deleted
    1
    -
    
    2
    -LIBRARY "libHSghc-internal-@LibVersion@-ghc@ProjectVersion@.dll"
    
    3
    -
    
    4
    -EXPORTS
    
    5
    -
    
    6
    -	ghczminternal_GHCziInternalziTypes_True_closure
    
    7
    -	ghczminternal_GHCziInternalziTypes_False_closure
    
    8
    -	ghczminternal_GHCziInternalziTypes_Czh_con_info
    
    9
    -	ghczminternal_GHCziInternalziTypes_Izh_con_info
    
    10
    -	ghczminternal_GHCziInternalziTypes_Fzh_con_info
    
    11
    -	ghczminternal_GHCziInternalziTypes_Dzh_con_info
    
    12
    -	ghczminternal_GHCziInternalziTypes_Wzh_con_info
    
    13
    -	ghczminternal_GHCziInternalziTypes_Czh_static_info
    
    14
    -	ghczminternal_GHCziInternalziTypes_Izh_static_info

  • utils/ghc-toolchain/exe/Main.hs
    ... ... @@ -56,6 +56,7 @@ data Opts = Opts
    56 56
         , optOpt       :: ProgOpt
    
    57 57
         , optLlvmAs    :: ProgOpt
    
    58 58
         , optWindres   :: ProgOpt
    
    59
    +    , optDlltool   :: ProgOpt
    
    59 60
         , optOtool     :: ProgOpt
    
    60 61
         , optInstallNameTool :: ProgOpt
    
    61 62
         -- Note we don't actually configure LD into anything but
    
    ... ... @@ -114,6 +115,7 @@ emptyOpts = Opts
    114 115
         , optOpt       = po0
    
    115 116
         , optLlvmAs    = po0
    
    116 117
         , optWindres   = po0
    
    118
    +    , optDlltool   = po0
    
    117 119
         , optLd        = po0
    
    118 120
         , optOtool     = po0
    
    119 121
         , optInstallNameTool = po0
    
    ... ... @@ -132,7 +134,7 @@ emptyOpts = Opts
    132 134
     
    
    133 135
     _optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr,
    
    134 136
         _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs,
    
    135
    -    _optWindres, _optLd, _optOtool, _optInstallNameTool
    
    137
    +    _optWindres, _optDlltool, _optLd, _optOtool, _optInstallNameTool
    
    136 138
         :: Lens Opts ProgOpt
    
    137 139
     _optCc      = Lens optCc      (\x o -> o {optCc=x})
    
    138 140
     _optCxx     = Lens optCxx     (\x o -> o {optCxx=x})
    
    ... ... @@ -150,6 +152,7 @@ _optLlc = Lens optLlc (\x o -> o {optLlc=x})
    150 152
     _optOpt     = Lens optOpt     (\x o -> o {optOpt=x})
    
    151 153
     _optLlvmAs  = Lens optLlvmAs  (\x o -> o {optLlvmAs=x})
    
    152 154
     _optWindres = Lens optWindres (\x o -> o {optWindres=x})
    
    155
    +_optDlltool = Lens optDlltool (\x o -> o {optDlltool=x})
    
    153 156
     _optLd      = Lens optLd (\x o -> o {optLd=x})
    
    154 157
     _optOtool   = Lens optOtool (\x o -> o {optOtool=x})
    
    155 158
     _optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x})
    
    ... ... @@ -218,6 +221,7 @@ options =
    218 221
         , progOpts "opt" "LLVM opt utility" _optOpt
    
    219 222
         , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs
    
    220 223
         , progOpts "windres" "windres utility" _optWindres
    
    224
    +    , progOpts "dlltool" "Windows dll utility" _optDlltool
    
    221 225
         , progOpts "ld" "linker" _optLd
    
    222 226
         , progOpts "otool" "otool utility" _optOtool
    
    223 227
         , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool
    
    ... ... @@ -481,12 +485,13 @@ mkTarget opts = do
    481 485
         llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"]
    
    482 486
     
    
    483 487
         -- Windows-specific utilities
    
    484
    -    windres <-
    
    488
    +    (windres, dlltool) <-
    
    485 489
             case archOS_OS archOs of
    
    486 490
               OSMinGW32 -> do
    
    487
    -            windres <- findProgram "windres" (optWindres opts) ["windres"]
    
    488
    -            return (Just windres)
    
    489
    -          _ -> return Nothing
    
    491
    +            windres <- findProgram "windres" (optWindres opts) ["windres", "llvm-windres"]
    
    492
    +            dlltool <- findProgram "dlltool" (optDlltool opts) ["dlltool", "llvm-dlltool"]
    
    493
    +            return (Just windres, Just dlltool)
    
    494
    +          _ -> return (Nothing, Nothing)
    
    490 495
     
    
    491 496
         -- Darwin-specific utilities
    
    492 497
         (otool, installNameTool) <-
    
    ... ... @@ -541,6 +546,7 @@ mkTarget opts = do
    541 546
                        , tgtOpt = opt
    
    542 547
                        , tgtLlvmAs = llvmAs
    
    543 548
                        , tgtWindres = windres
    
    549
    +                   , tgtDlltool = dlltool
    
    544 550
                        , tgtOtool = otool
    
    545 551
                        , tgtInstallNameTool = installNameTool
    
    546 552
                        , tgtWordSize
    

  • utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
    ... ... @@ -93,6 +93,7 @@ data Target = Target
    93 93
     
    
    94 94
           -- Windows-specific tools
    
    95 95
         , tgtWindres :: Maybe Program
    
    96
    +    , tgtDlltool :: Maybe Program
    
    96 97
     
    
    97 98
           -- Darwin-specific tools
    
    98 99
         , tgtOtool   :: Maybe Program
    
    ... ... @@ -150,6 +151,7 @@ instance Show Target where
    150 151
         , ", tgtOpt = " ++ show tgtOpt
    
    151 152
         , ", tgtLlvmAs = " ++ show tgtLlvmAs
    
    152 153
         , ", tgtWindres = " ++ show tgtWindres
    
    154
    +    , ", tgtDlltool = " ++ show tgtDlltool
    
    153 155
         , ", tgtOtool = " ++ show tgtOtool
    
    154 156
         , ", tgtInstallNameTool = " ++ show tgtInstallNameTool
    
    155 157
         , "}"