Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • hadrian/src/Settings/Builders/DeriveConstants.hs
    ... ... @@ -48,4 +48,4 @@ includeCcArgs = do
    48 48
                 , arg "-Irts/include"
    
    49 49
                 , arg $ "-I" ++ rtsPath </> "include"
    
    50 50
                 , notM targetSupportsSMP ? arg "-DNOSMP"
    
    51
    -            , arg "-fcommon" ]
    51
    +            ]

  • utils/deriveConstants/Main.hs
    1
    +{-# LANGUAGE LambdaCase #-}
    
    2
    +
    
    1 3
     {- ------------------------------------------------------------------------
    
    2 4
     
    
    3 5
     (c) The GHC Team, 1992-2012
    
    ... ... @@ -65,7 +67,17 @@ main = do opts <- parseArgs
    65 67
                                     "mingw32" -> Windows
    
    66 68
                                     _         -> DefaultOS
    
    67 69
                              verbose = o_verbose opts
    
    68
    -                         gccFlags = o_gccFlags opts
    
    70
    +                         gccFlags0 = o_gccFlags opts
    
    71
    +                          -- nm applied to COFF files doesn't correctly report
    
    72
    +                          -- the size of global variable symbols (it reports 0)
    
    73
    +                          -- except for Common symbols (probably because the
    
    74
    +                          -- merge algorithm of Common symbols takes symbol size
    
    75
    +                          -- into account). So we force the use of `-fcommon`
    
    76
    +                          -- here.
    
    77
    +                          -- As far as we know, it is only required on Windows
    
    78
    +                          -- but enabling it on other platforms does no harm, so
    
    79
    +                          -- we enable it unconditionally.
    
    80
    +                         gccFlags = "-fcommon" : gccFlags0
    
    69 81
                          rs <- case os of
    
    70 82
                                  JS -> getWantedJS
    
    71 83
                                  _  -> getWanted verbose os tmpdir gccProg gccFlags nmProg
    
    ... ... @@ -751,7 +763,7 @@ getWanted verbose os tmpdir gccProgram gccFlags nmProgram mobjdumpProgram
    751 763
                                   ++ "Workaround: You may want to pass\n"
    
    752 764
                                   ++ "    --with-nm=$(xcrun --find nm-classic)\n"
    
    753 765
                                   ++ "to 'configure'.\n"
    
    754
    -             Just x     -> die ("unexpected value round-tripped for CONTROL_GROUP_CONST_291: " ++ show x)
    
    766
    +             Just x     -> die ("unexpected value round-tripped for CONTROL_GROUP_CONST_291: " ++ show x ++ "\n" ++ show m ++ "\n" ++ xs)
    
    755 767
     
    
    756 768
              mapM (lookupResult m) (wanteds (Just os))
    
    757 769
         where headers = ["#define IN_STG_CODE 0",
    
    ... ... @@ -841,14 +853,23 @@ getWanted verbose os tmpdir gccProgram gccFlags nmProgram mobjdumpProgram
    841 853
               -- and returns ("MAX_Vanilla_REG", 11)
    
    842 854
               parseNmLine line
    
    843 855
                   = case words line of
    
    844
    -                ('_' : n) : "C" : s : _ -> mkP n s
    
    845
    -                n : "C" : s : _ -> mkP n s
    
    846
    -                [n, "D", _, s] -> mkP n s
    
    847
    -                [s, "O", "*COM*", _, n] -> mkP n s
    
    856
    +                -- in common section
    
    857
    +                (n : "C" : s : _ )           -> mkP n s -- nm format (ELF, COFF)
    
    858
    +                [s, "O", "*COM*", _, n]      -> mkP n s -- objdump format (ELF)
    
    859
    +                -- in .bss section
    
    860
    +                [n, "B", _, s ]              -> mkP n s -- nm format (ELF)
    
    861
    +                [_, "g", "O", ".bss", s, n]  -> mkP n s -- objdump format (ELF)
    
    862
    +                -- in data section
    
    863
    +                [n, "D", _, s]               -> mkP n s -- nm format (ELF)
    
    864
    +                [_, "g", "O", ".data", s, n] -> mkP n s -- objdump format (ELF)
    
    848 865
                     _ -> Nothing
    
    849
    -              where mkP r s = case (stripPrefix prefix r, readHex s) of
    
    866
    +              where mkP r s = case (stripPrefix prefix (strip_ r), readHex s) of
    
    850 867
                             (Just name, [(size, "")]) -> Just (name, size)
    
    851 868
                             _ -> Nothing
    
    869
    +                    -- strip leading underscore: some platforms (e.g. Darwin) add one
    
    870
    +                    strip_ = \case
    
    871
    +                      ('_':n) -> n
    
    872
    +                      n       -> n
    
    852 873
     
    
    853 874
               -- On AIX, `nm` isn't able to tell us the symbol size, so we
    
    854 875
               -- need to use `objdump --syms`. However, unlike on OpenBSD,