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:

11 changed files:

Changes:

  • compiler/GHC/Driver/Session.hs
    ... ... @@ -3499,6 +3499,7 @@ compilerInfo dflags
    3499 3499
            ("target word size", query $ show . wordSize2Bytes . tgtWordSize),
    
    3500 3500
            ("target word big endian", queryBool $ (\case BigEndian -> True; LittleEndian -> False) . tgtEndianness),
    
    3501 3501
            ("target has GNU nonexec stack", queryBool tgtSupportsGnuNonexecStack),
    
    3502
    +       ("target has libm", queryBool tgtHasLibm),
    
    3502 3503
            ("target has .ident directive", queryBool tgtSupportsIdentDirective),
    
    3503 3504
            ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols),
    
    3504 3505
            ("Unregisterised", queryBool tgtUnregisterised),
    

  • compiler/GHC/Settings/IO.hs
    ... ... @@ -97,10 +97,6 @@ initSettings top_dir = do
    97 97
           getTool :: (Target -> Program) -> (String, [String])
    
    98 98
           getTool key = (getToolPath key, getToolFlags key)
    
    99 99
     
    
    100
    -  -- See Note [Settings file] for a little more about this file. We're
    
    101
    -  -- just partially applying those functions and throwing 'Left's; they're
    
    102
    -  -- written in a very portable style to keep ghc-boot light.
    
    103
    -  targetHasLibm <- getBooleanSetting "target has libm"
    
    104 100
       let
    
    105 101
         (cc_prog, cc_args0)  = getTool (ccProgram . tgtCCompiler)
    
    106 102
         (cxx_prog, cxx_args) = getTool (cxxProgram . tgtCxxCompiler)
    
    ... ... @@ -109,7 +105,7 @@ initSettings top_dir = do
    109 105
         (js_cpp_prog, js_cpp_args) = getTool (maybe (Program "" []) jsCppProgram . tgtJsCPreprocessor)
    
    110 106
         (cmmCpp_prog, cmmCpp_args) = getTool (cmmCppProgram . tgtCmmCPreprocessor)
    
    111 107
     
    
    112
    -    platform = getTargetPlatform targetHasLibm target
    
    108
    +    platform = getTargetPlatform target
    
    113 109
     
    
    114 110
         unreg_cc_args = if platformUnregisterised platform
    
    115 111
                         then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
    
    ... ... @@ -242,8 +238,8 @@ initSettings top_dir = do
    242 238
         , sRawTarget      = target
    
    243 239
         }
    
    244 240
     
    
    245
    -getTargetPlatform :: Bool {-^ Does target have libm -} -> Target -> Platform
    
    246
    -getTargetPlatform targetHasLibm Target{..} = Platform
    
    241
    +getTargetPlatform :: Target -> Platform
    
    242
    +getTargetPlatform Target{..} = Platform
    
    247 243
         { platformArchOS    = tgtArchOs
    
    248 244
         , platformWordSize  = case tgtWordSize of WS4 -> PW4
    
    249 245
                                                   WS8 -> PW8
    
    ... ... @@ -255,6 +251,6 @@ getTargetPlatform targetHasLibm Target{..} = Platform
    255 251
         , platformIsCrossCompiling = not tgtLocallyExecutable
    
    256 252
         , platformLeadingUnderscore = tgtSymbolsHaveLeadingUnderscore
    
    257 253
         , platformTablesNextToCode  = tgtTablesNextToCode
    
    258
    -    , platformHasLibm = targetHasLibm
    
    254
    +    , platformHasLibm = tgtHasLibm
    
    259 255
         , platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit
    
    260 256
         }

  • hadrian/bindist/Makefile
    ... ... @@ -85,8 +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 '[("target has libm", "$(TargetHasLibm)")' >> $@
    
    89
    -	@echo ',("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    88
    +	@echo '[("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
    
    90 89
     	@echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@
    
    91 90
     	@echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@
    
    92 91
     	@echo ',("Support SMP", "$(GhcWithSMP)")' >> $@
    

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

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

  • hadrian/cfg/system.config.in
    ... ... @@ -81,8 +81,6 @@ project-git-commit-id = @ProjectGitCommitId@
    81 81
     # See Note [tooldir: How GHC finds mingw on Windows]
    
    82 82
     settings-use-distro-mingw = @EnableDistroToolchain@
    
    83 83
     
    
    84
    -target-has-libm = @TargetHasLibm@
    
    85
    -
    
    86 84
     # Include and library directories:
    
    87 85
     #=================================
    
    88 86
     
    

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -427,7 +427,7 @@ bindistRules = do
    427 427
         , interpolateSetting "ProjectVersion" ProjectVersion
    
    428 428
         , interpolateVar "EnableDistroToolchain" $ lookupSystemConfig "settings-use-distro-mingw"
    
    429 429
         , interpolateVar "TablesNextToCode" $ yesNo <$> getTarget tgtTablesNextToCode
    
    430
    -    , interpolateVar "TargetHasLibm" $ lookupSystemConfig "target-has-libm"
    
    430
    +    , interpolateVar "TargetHasLibm" $ yesNo <$> getTarget tgtHasLibm
    
    431 431
         , interpolateVar "TargetPlatform" $ getTarget targetPlatformTriple
    
    432 432
         , interpolateVar "TargetWordBigEndian" $ getTarget isBigEndian
    
    433 433
         , interpolateVar "TargetWordSize" $ getTarget wordSize
    
    ... ... @@ -484,7 +484,6 @@ generateSettings settingsFile = do
    484 484
     
    
    485 485
         settings <- traverse sequence $
    
    486 486
             [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
    
    487
    -        , ("target has libm", expr $  lookupSystemConfig "target-has-libm")
    
    488 487
             , ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs)
    
    489 488
             , ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
    
    490 489
             , ("Support SMP", expr $ yesNo <$> targetSupportsSMP)
    

  • m4/prep_target_file.m4
    ... ... @@ -157,6 +157,7 @@ AC_DEFUN([PREP_TARGET_FILE],[
    157 157
         PREP_BOOLEAN([Unregisterised])
    
    158 158
         PREP_BOOLEAN([TablesNextToCode])
    
    159 159
         PREP_BOOLEAN([UseLibffiForAdjustors])
    
    160
    +    PREP_BOOLEAN([TargetHasLibm])
    
    160 161
         PREP_BOOLEAN([ArIsGNUAr])
    
    161 162
         PREP_BOOLEAN([ArNeedsRanLib])
    
    162 163
         PREP_NOT_BOOLEAN([CrossCompiling])
    

  • utils/ghc-toolchain/exe/Main.hs
    ... ... @@ -486,6 +486,7 @@ mkTarget opts = do
    486 486
         tgtSupportsSubsectionsViaSymbols <- checkSubsectionsViaSymbols archOs cc
    
    487 487
         tgtSupportsIdentDirective <- checkIdentDirective cc
    
    488 488
         tgtSupportsGnuNonexecStack <- checkGnuNonexecStack archOs cc
    
    489
    +    tgtHasLibm <- checkTargetHasLibm cc
    
    489 490
     
    
    490 491
         -- code generator configuration
    
    491 492
         tgtUnregisterised <- determineUnregisterised archOs (optUnregisterised opts)
    
    ... ... @@ -526,6 +527,7 @@ mkTarget opts = do
    526 527
                        , tgtUnregisterised
    
    527 528
                        , tgtTablesNextToCode
    
    528 529
                        , tgtUseLibffiForAdjustors = tgtUseLibffi
    
    530
    +                   , tgtHasLibm
    
    529 531
                        , tgtSymbolsHaveLeadingUnderscore
    
    530 532
                        , tgtSupportsSubsectionsViaSymbols
    
    531 533
                        , tgtSupportsIdentDirective
    

  • utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
    ... ... @@ -5,6 +5,7 @@ module GHC.Toolchain.PlatformDetails
    5 5
         , checkSubsectionsViaSymbols
    
    6 6
         , checkIdentDirective
    
    7 7
         , checkGnuNonexecStack
    
    8
    +    , checkTargetHasLibm
    
    8 9
         ) where
    
    9 10
     
    
    10 11
     import Data.List (isInfixOf)
    
    ... ... @@ -112,8 +113,6 @@ checkEndianness__BYTE_ORDER__ cc = checking "endianness (__BYTE_ORDER__)" $ do
    112 113
             , "#endif"
    
    113 114
             ]
    
    114 115
     
    
    115
    -
    
    116
    -
    
    117 116
     checkLeadingUnderscore :: Cc -> Nm -> M Bool
    
    118 117
     checkLeadingUnderscore cc nm = checking ctxt $ withTempDir $ \dir -> do
    
    119 118
         let test_o = dir </> "test.o"
    
    ... ... @@ -156,6 +155,21 @@ checkGnuNonexecStack archOs =
    156 155
                        , asmStmt ".section .text"
    
    157 156
                        ]
    
    158 157
     
    
    158
    +checkTargetHasLibm :: Cc -> M Bool
    
    159
    +checkTargetHasLibm cc0 = testCompile "whether target has libm" prog cc
    
    160
    +  where
    
    161
    +    cc = cc0 & _ccProgram % _prgFlags %++ "-lm"
    
    162
    +    prog = unlines
    
    163
    +        [ "char atan (void);"
    
    164
    +        , "int"
    
    165
    +        , "main (void)"
    
    166
    +        , "{"
    
    167
    +        , "return atan ();"
    
    168
    +        , "  ;"
    
    169
    +        , "  return 0;"
    
    170
    +        , "}"
    
    171
    +        ]
    
    172
    +
    
    159 173
     asmStmt :: String -> String
    
    160 174
     asmStmt s = "__asm__(\"" ++ foldMap escape s ++ "\");"
    
    161 175
       where
    

  • utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
    ... ... @@ -57,6 +57,10 @@ data Target = Target
    57 57
         , tgtUseLibffiForAdjustors :: Bool
    
    58 58
         -- ^ We need to know whether or not to include libffi headers, and generate additional code for it
    
    59 59
     
    
    60
    +      -- Target support
    
    61
    +    , tgtHasLibm :: Bool
    
    62
    +    -- ^ Does this target have a libm library that should always be linked against?
    
    63
    +
    
    60 64
           -- C toolchain
    
    61 65
         , tgtCCompiler :: Cc
    
    62 66
         , tgtCxxCompiler :: Cxx
    
    ... ... @@ -121,6 +125,7 @@ instance Show Target where
    121 125
         , ", tgtUnregisterised = " ++ show tgtUnregisterised
    
    122 126
         , ", tgtTablesNextToCode = " ++ show tgtTablesNextToCode
    
    123 127
         , ", tgtUseLibffiForAdjustors = " ++ show tgtUseLibffiForAdjustors
    
    128
    +    , ", tgtHasLibm = " ++ show tgtHasLibm
    
    124 129
         , ", tgtCCompiler = " ++ show tgtCCompiler
    
    125 130
         , ", tgtCxxCompiler = " ++ show tgtCxxCompiler
    
    126 131
         , ", tgtCPreprocessor = " ++ show tgtCPreprocessor