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

Commits:

4 changed files:

Changes:

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -3502,6 +3502,7 @@ compilerInfo dflags
    3502 3502
            ("target has .ident directive", queryBool tgtSupportsIdentDirective),
    
    3503 3503
            ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols),
    
    3504 3504
            ("target RTS linker only supports shared libraries", queryBool tgtRTSLinkerOnlySupportsSharedLibs),
    
    3505
    +       ("unlit command", toolSettings_pgm_L (toolSettings dflags)),
    
    3505 3506
            ("Unregisterised", queryBool tgtUnregisterised),
    
    3506 3507
            ("LLVM target", query tgtLlvmTarget),
    
    3507 3508
            ("LLVM llc command", queryCmdMaybe id tgtLlc),
    
    ... ... @@ -3528,6 +3529,10 @@ compilerInfo dflags
    3528 3529
            ("target os string",            stringEncodeOS (platformOS (targetPlatform dflags))),
    
    3529 3530
            ("target arch string",          stringEncodeArch (platformArch (targetPlatform dflags))),
    
    3530 3531
            ("target word size in bits",    show (platformWordSizeInBits (targetPlatform dflags))),
    
    3532
    +       -- keep "duplicate" of "Have interpreter" for backwards compatibility,
    
    3533
    +       -- since we used to show both...
    
    3534
    +       -- These should really be called "Has internal interpreter"
    
    3535
    +       ("Use interpreter",             showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
    
    3531 3536
            ("Have interpreter",            showBool $ platformMisc_ghcWithInterpreter $ platformMisc dflags),
    
    3532 3537
            ("Object splitting supported",  showBool False),
    
    3533 3538
            ("Have native code generator",  showBool $ platformNcgSupported platform),
    

  • compiler/GHC/Settings/IO.hs
    1
    +{-# LANGUAGE CPP #-}
    
    1 2
     {-# LANGUAGE RecordWildCards #-}
    
    2 3
     {-# LANGUAGE LambdaCase #-}
    
    3 4
     {-# LANGUAGE ScopedTypeVariables #-}
    
    ... ... @@ -130,12 +131,8 @@ initSettings top_dir = do
    130 131
       let ghc_usage_msg_path  = installed "ghc-usage.txt"
    
    131 132
           ghci_usage_msg_path = installed "ghci-usage.txt"
    
    132 133
     
    
    133
    -  -- For all systems, unlit, split, mangle are GHC utilities
    
    134
    -  -- architecture-specific stuff is done when building Config.hs
    
    135
    -  unlit_path <- getToolSetting "unlit command"
    
    136
    -
    
    137
    -  -- Other things being equal, 'as' is simply 'gcc'
    
    138
    -  let (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink)
    
    134
    +      -- Other things being equal, 'as' is simply 'gcc'
    
    135
    +      (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink)
    
    139 136
           as_prog      = cc_prog
    
    140 137
           as_args      = map Option cc_args
    
    141 138
           ld_prog      = cc_link
    
    ... ... @@ -145,8 +142,9 @@ initSettings top_dir = do
    145 142
             let (ld_r_path, ld_r_args) = getTool (mergeObjsProgram . const ld_r_prog)
    
    146 143
             pure (ld_r_path, map Option ld_r_args)
    
    147 144
           iserv_prog   = libexec "ghc-iserv"
    
    148
    -
    
    149
    -  ghcWithInterpreter <- getBooleanSetting "Use interpreter"
    
    145
    +      unlit_prog   = libexec (if tgtLocallyExecutable
    
    146
    +                                  then "unlit" -- not a cross compiler
    
    147
    +                                  else targetPlatformTriple target ++ "-unlit")
    
    150 148
     
    
    151 149
       baseUnitId <- getSetting_raw "base unit-id"
    
    152 150
     
    
    ... ... @@ -181,7 +179,7 @@ initSettings top_dir = do
    181 179
           , toolSettings_arSupportsDashL  = arSupportsDashL  $ tgtAr target
    
    182 180
           , toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0 $ tgtCmmCPreprocessor target
    
    183 181
     
    
    184
    -      , toolSettings_pgm_L       = unlit_path
    
    182
    +      , toolSettings_pgm_L       = unlit_prog
    
    185 183
           , toolSettings_pgm_P       = (hs_cpp_prog, map Option hs_cpp_args)
    
    186 184
           , toolSettings_pgm_JSP     = (js_cpp_prog, map Option js_cpp_args)
    
    187 185
           , toolSettings_pgm_CmmP    = (cmmCpp_prog, map Option cmmCpp_args)
    
    ... ... @@ -227,7 +225,7 @@ initSettings top_dir = do
    227 225
         , sTargetPlatform = platform
    
    228 226
         , sPlatformMisc = PlatformMisc
    
    229 227
           { platformMisc_targetPlatformString = targetPlatformTriple target
    
    230
    -      , platformMisc_ghcWithInterpreter = ghcWithInterpreter
    
    228
    +      , platformMisc_ghcWithInterpreter = ghcWithInternalInterpreter
    
    231 229
           , platformMisc_libFFI = tgtUseLibffiForAdjustors target
    
    232 230
           , platformMisc_llvmTarget = tgtLlvmTarget target
    
    233 231
           , platformMisc_targetRTSLinkerOnlySupportsSharedLibs = tgtRTSLinkerOnlySupportsSharedLibs target
    
    ... ... @@ -253,3 +251,13 @@ getTargetPlatform Target{..} = Platform
    253 251
         , platformHasLibm = tgtHasLibm
    
    254 252
         , platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit
    
    255 253
         }
    
    254
    +
    
    255
    +
    
    256
    +-- | Do we have an internal interpreter?
    
    257
    +ghcWithInternalInterpreter :: Bool
    
    258
    +#if defined(HAVE_INTERNAL_INTERPRETER)
    
    259
    +ghcWithInternalInterpreter = True
    
    260
    +#else
    
    261
    +ghcWithInternalInterpreter = False
    
    262
    +#endif
    
    263
    +

  • hadrian/bindist/Makefile
    ... ... @@ -85,9 +85,7 @@ WrapperBinsDir=${bindir}
    85 85
     # N.B. this is duplicated from includes/ghc.mk.
    
    86 86
     lib/settings : config.mk
    
    87 87
     	@rm -f $@
    
    88
    -	@echo '[("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    89
    -	@echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@
    
    90
    -	@echo ',("RTS ways", "$(GhcRTSWays)")' >> $@
    
    88
    +	@echo '[("RTS ways", "$(GhcRTSWays)")' >> $@
    
    91 89
     	@echo ',("Relative Global Package DB", "package.conf.d")' >> $@
    
    92 90
     	@echo ',("base unit-id", "$(BaseUnitId)")' >> $@
    
    93 91
     	@echo "]" >> $@
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -8,7 +8,6 @@ import Development.Shake.FilePath
    8 8
     import Data.Char (isSpace)
    
    9 9
     import qualified Data.Set as Set
    
    10 10
     import Base
    
    11
    -import qualified Context
    
    12 11
     import Expression
    
    13 12
     import Hadrian.Oracles.TextFile (lookupSystemConfig, getTargetTarget)
    
    14 13
     import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL)
    
    ... ... @@ -25,7 +24,6 @@ import Utilities
    25 24
     
    
    26 25
     import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp))
    
    27 26
     import GHC.Platform.ArchOS
    
    28
    -import Settings.Program (ghcWithInterpreter)
    
    29 27
     
    
    30 28
     -- | Track this file to rebuild generated files whenever it changes.
    
    31 29
     trackGenerateHs :: Expr ()
    
    ... ... @@ -461,7 +459,6 @@ ghcWrapper stage = do
    461 459
     
    
    462 460
     generateSettings :: FilePath -> Expr String
    
    463 461
     generateSettings settingsFile = do
    
    464
    -    ctx <- getContext
    
    465 462
         stage <- getStage
    
    466 463
     
    
    467 464
         package_db_path <- expr $ do
    
    ... ... @@ -483,9 +480,7 @@ generateSettings settingsFile = do
    483 480
         let rel_pkg_db = makeRelativeNoSysLink (dropFileName settingsFile) package_db_path
    
    484 481
     
    
    485 482
         settings <- traverse sequence $
    
    486
    -        [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
    
    487
    -        , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
    
    488
    -        , ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
    
    483
    +        [ ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
    
    489 484
             , ("Relative Global Package DB", pure rel_pkg_db)
    
    490 485
             , ("base unit-id", pure base_unit_id)
    
    491 486
             ]