Cheng Shao pushed to branch wip/symbolizer at Glasgow Haskell Compiler / GHC

Commits:

18 changed files:

Changes:

  • compiler/GHC/Cmm/GenerateDebugSymbolStub.hs
    1
    +{-# LANGUAGE MultiWayIf #-}
    
    2
    +{-# LANGUAGE Strict #-}
    
    3
    +
    
    4
    +module GHC.Cmm.GenerateDebugSymbolStub
    
    5
    +  ( generateDebugSymbolStub,
    
    6
    +  )
    
    7
    +where
    
    8
    +
    
    9
    +import Control.Monad
    
    10
    +import Control.Monad.IO.Class
    
    11
    +import Data.Foldable
    
    12
    +import Data.Functor
    
    13
    +import Data.IORef
    
    14
    +import Data.List (isSuffixOf)
    
    15
    +import Data.Map.Strict qualified as Map
    
    16
    +import Data.Maybe
    
    17
    +import GHC.Cmm
    
    18
    +import GHC.Cmm.CLabel
    
    19
    +import GHC.Cmm.Dataflow.Label qualified as H
    
    20
    +import GHC.Data.FastString
    
    21
    +import GHC.Data.Stream (Stream)
    
    22
    +import GHC.Data.Stream qualified as Stream
    
    23
    +import GHC.Platform
    
    24
    +import GHC.Prelude
    
    25
    +import GHC.Types.ForeignStubs
    
    26
    +import GHC.Unit.Types
    
    27
    +import GHC.Utils.Outputable
    
    28
    +
    
    29
    +generateDebugSymbolStub ::
    
    30
    +  (MonadIO m) =>
    
    31
    +  Platform ->
    
    32
    +  Module ->
    
    33
    +  Stream m RawCmmGroup r ->
    
    34
    +  Stream m RawCmmGroup (r, CStub)
    
    35
    +generateDebugSymbolStub platform this_mod rawcmms0 = do
    
    36
    +  (lbls_ref, per_group) <- liftIO $ do
    
    37
    +    lbls_ref <- newIORef Map.empty
    
    38
    +    let per_group decls = for_ decls per_decl $> decls
    
    39
    +        per_decl (CmmData _ (CmmStaticsRaw lbl _)) =
    
    40
    +          liftIO
    
    41
    +            $ when (externallyVisibleCLabel lbl)
    
    42
    +            $ modifyIORef' lbls_ref
    
    43
    +            $ Map.insert lbl (data_label_type lbl)
    
    44
    +        per_decl (CmmProc h lbl _ _) = case H.mapToList h of
    
    45
    +          [] ->
    
    46
    +            liftIO
    
    47
    +              $ when (externallyVisibleCLabel lbl)
    
    48
    +              $ modifyIORef' lbls_ref
    
    49
    +              $ Map.insert lbl (proc_label_type lbl)
    
    50
    +          hs -> for_ hs $ \(_, CmmStaticsRaw lbl _) ->
    
    51
    +            liftIO
    
    52
    +              $ when (externallyVisibleCLabel lbl)
    
    53
    +              $ modifyIORef' lbls_ref
    
    54
    +              $ Map.insert lbl (data_label_type lbl)
    
    55
    +        data_label_type lbl
    
    56
    +          | "_closure"
    
    57
    +              `isSuffixOf` str
    
    58
    +              && not
    
    59
    +                (str `elem` ["stg_CHARLIKE_closure", "stg_INTLIKE_closure"]) =
    
    60
    +              Just ("extern StgClosure ", "")
    
    61
    +          | "_str" `isSuffixOf` str =
    
    62
    +              Just ("EB_(", ")")
    
    63
    +          | str
    
    64
    +              `elem` [ "stg_arg_bitmaps",
    
    65
    +                       "stg_ap_stack_entries",
    
    66
    +                       "stg_stack_save_entries"
    
    67
    +                     ] =
    
    68
    +              Just ("ERO_(", ")")
    
    69
    +          | str
    
    70
    +              `elem` [ "no_break_on_exception",
    
    71
    +                       "stg_scheduler_loop_epoch",
    
    72
    +                       "stg_scheduler_loop_tid"
    
    73
    +                     ] =
    
    74
    +              Just ("ERW_(", ")")
    
    75
    +          | str
    
    76
    +              `elem` [ "stg_gc_prim_p_ll_info",
    
    77
    +                       "stg_gc_prim_pp_ll_info",
    
    78
    +                       "stg_JSVAL_info",
    
    79
    +                       "stg_scheduler_loop_info"
    
    80
    +                     ] =
    
    81
    +              Just ("extern const StgInfoTable ", "")
    
    82
    +          | not $ needsCDecl lbl =
    
    83
    +              Nothing
    
    84
    +          | "_cc" `isSuffixOf` str =
    
    85
    +              Just ("extern CostCentre ", "[]")
    
    86
    +          | "_ccs" `isSuffixOf` str =
    
    87
    +              Just ("extern CostCentreStack ", "[]")
    
    88
    +          | "_ipe_buf" `isSuffixOf` str =
    
    89
    +              Just ("extern IpeBufferListNode ", "")
    
    90
    +          | otherwise =
    
    91
    +              Just ("ERW_(", ")")
    
    92
    +          where
    
    93
    +            str =
    
    94
    +              showSDocOneLine defaultSDocContext {sdocStyle = PprCode}
    
    95
    +                $ pprCLabel platform lbl
    
    96
    +        proc_label_type _ = Just ("EF_(", ")")
    
    97
    +    pure (lbls_ref, per_group)
    
    98
    +  r <- Stream.mapM per_group rawcmms0
    
    99
    +  liftIO $ do
    
    100
    +    lbls <- Map.toList <$> readIORef lbls_ref
    
    101
    +    let ctor_lbl = mkInitializerStubLabel this_mod $ fsLit "symbolizer"
    
    102
    +        entries_lbl =
    
    103
    +          mkInitializerStubLabel this_mod $ fsLit "symbolizer_entries"
    
    104
    +        ctor_decls =
    
    105
    +          vcat
    
    106
    +            [ text lbl_type_l
    
    107
    +                <> pprCLabel platform lbl
    
    108
    +                <> text lbl_type_r
    
    109
    +                <> semi
    
    110
    +            | (lbl, maybe_lbl_type) <- lbls,
    
    111
    +              (lbl_type_l, lbl_type_r) <- maybeToList maybe_lbl_type
    
    112
    +            ]
    
    113
    +            <> text "static const DebugSymbolEntry "
    
    114
    +            <> pprCLabel platform entries_lbl
    
    115
    +            <> text "[] = "
    
    116
    +            <> braces
    
    117
    +              ( hsep
    
    118
    +                  $ punctuate
    
    119
    +                    comma
    
    120
    +                    [ braces
    
    121
    +                        $ text ".addr = (void*)&"
    
    122
    +                        <> pprCLabel platform lbl
    
    123
    +                        <> comma
    
    124
    +                        <> text ".sym = "
    
    125
    +                        <> doubleQuotes (pprCLabel platform lbl)
    
    126
    +                    | (lbl, _) <- lbls
    
    127
    +                    ]
    
    128
    +              )
    
    129
    +            <> semi
    
    130
    +        ctor_body =
    
    131
    +          text "registerDebugSymbol"
    
    132
    +            <> parens
    
    133
    +              (pprCLabel platform entries_lbl <> comma <> int (length lbls))
    
    134
    +            <> semi
    
    135
    +        cstub = case lbls of
    
    136
    +          [] -> mempty
    
    137
    +          _ -> initializerCStub platform ctor_lbl ctor_decls ctor_body
    
    138
    +    pure (r, cstub)

  • compiler/GHC/Driver/CodeOutput.hs
    ... ... @@ -26,6 +26,7 @@ import GHC.CmmToC ( cmmToC )
    26 26
     import GHC.Cmm.Lint         ( cmmLint )
    
    27 27
     import GHC.Cmm
    
    28 28
     import GHC.Cmm.CLabel
    
    29
    +import GHC.Cmm.GenerateDebugSymbolStub
    
    29 30
     
    
    30 31
     import GHC.StgToCmm.CgUtils (CgStream)
    
    31 32
     
    
    ... ... @@ -76,7 +77,8 @@ import qualified Data.Set as Set
    76 77
     
    
    77 78
     codeOutput
    
    78 79
         :: forall a.
    
    79
    -       Logger
    
    80
    +       Platform
    
    81
    +    -> Logger
    
    80 82
         -> TmpFs
    
    81 83
         -> LlvmConfigCache
    
    82 84
         -> DynFlags
    
    ... ... @@ -95,7 +97,7 @@ codeOutput
    95 97
                (Bool{-stub_h_exists-}, Maybe FilePath{-stub_c_exists-}),
    
    96 98
                [(ForeignSrcLang, FilePath)]{-foreign_fps-},
    
    97 99
                a)
    
    98
    -codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location genForeignStubs foreign_fps pkg_deps dus0
    
    100
    +codeOutput platform logger tmpfs llvm_config dflags unit_state this_mod filenm location genForeignStubs foreign_fps pkg_deps dus0
    
    99 101
       cmm_stream
    
    100 102
       =
    
    101 103
         do  {
    
    ... ... @@ -119,10 +121,12 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g
    119 121
                     ; return cmm
    
    120 122
                     }
    
    121 123
     
    
    124
    +              debug_cmm_stream = generateDebugSymbolStub platform this_mod linted_cmm_stream
    
    125
    +
    
    122 126
             ; let final_stream :: CgStream RawCmmGroup (ForeignStubs, a)
    
    123 127
                   final_stream = do
    
    124
    -                  { a <- linted_cmm_stream
    
    125
    -                  ; let stubs = genForeignStubs a
    
    128
    +                  { (a, debug_cstub) <- debug_cmm_stream
    
    129
    +                  ; let stubs = genForeignStubs a `appendStubC` debug_cstub
    
    126 130
                       ; emitInitializerDecls this_mod stubs
    
    127 131
                       ; return (stubs, a) }
    
    128 132
     
    

  • compiler/GHC/Driver/Main.hs
    ... ... @@ -2094,7 +2094,7 @@ hscGenHardCode hsc_env cgguts mod_loc output_filename = do
    2094 2094
     
    
    2095 2095
                   (output_filename, (_stub_h_exists, stub_c_exists), foreign_fps, cmm_cg_infos)
    
    2096 2096
                       <- {-# SCC "codeOutput" #-}
    
    2097
    -                    codeOutput logger tmpfs llvm_config dflags (hsc_units hsc_env) this_mod output_filename mod_loc
    
    2097
    +                    codeOutput platform logger tmpfs llvm_config dflags (hsc_units hsc_env) this_mod output_filename mod_loc
    
    2098 2098
                         foreign_stubs foreign_files dependencies (initDUniqSupply 'n' 0) rawcmms1
    
    2099 2099
                   return  ( output_filename, stub_c_exists, foreign_fps
    
    2100 2100
                           , Just stg_cg_infos, Just cmm_cg_infos)
    
    ... ... @@ -2248,7 +2248,7 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs
    2248 2248
                       in NoStubs `appendStubC` ip_init
    
    2249 2249
                   | otherwise     = NoStubs
    
    2250 2250
             (_output_filename, (_stub_h_exists, stub_c_exists), _foreign_fps, _caf_infos)
    
    2251
    -          <- codeOutput logger tmpfs llvm_config dflags (hsc_units hsc_env) cmm_mod output_filename no_loc foreign_stubs [] S.empty
    
    2251
    +          <- codeOutput platform logger tmpfs llvm_config dflags (hsc_units hsc_env) cmm_mod output_filename no_loc foreign_stubs [] S.empty
    
    2252 2252
                  dus1 rawCmms
    
    2253 2253
             return stub_c_exists
    
    2254 2254
       where
    

  • compiler/GHC/Iface/Tidy/StaticPtrTable.hs
    ... ... @@ -17,18 +17,18 @@
    17 17
     -- > static void hs_hpc_init_Main(void) {
    
    18 18
     -- >
    
    19 19
     -- >   static StgWord64 k0[2] = {16252233372134256ULL,7370534374096082ULL};
    
    20
    --- >   extern StgPtr Main_r2wb_closure;
    
    20
    +-- >   extern StgClosure Main_r2wb_closure;
    
    21 21
     -- >   hs_spt_insert(k0, &Main_r2wb_closure);
    
    22 22
     -- >
    
    23 23
     -- >   static StgWord64 k1[2] = {12545634534567898ULL,5409674567544151ULL};
    
    24
    --- >   extern StgPtr Main_r2wc_closure;
    
    24
    +-- >   extern StgClosure Main_r2wc_closure;
    
    25 25
     -- >   hs_spt_insert(k1, &Main_r2wc_closure);
    
    26 26
     -- >
    
    27 27
     -- > }
    
    28 28
     --
    
    29 29
     -- where the constants are fingerprints produced from the static forms.
    
    30 30
     --
    
    31
    --- The linker must find the definitions matching the @extern StgPtr <name>@
    
    31
    +-- The linker must find the definitions matching the @extern StgClosure <name>@
    
    32 32
     -- declarations. For this to work, the identifiers of static pointers need to be
    
    33 33
     -- exported. This is done in 'GHC.Core.Opt.SetLevels.newLvlVar'.
    
    34 34
     --
    
    ... ... @@ -256,7 +256,7 @@ sptModuleInitCode platform this_mod entries
    256 256
         init_fn_body = vcat
    
    257 257
             [  text "static StgWord64 k" <> int i <> text "[2] = "
    
    258 258
                <> pprFingerprint fp <> semi
    
    259
    -        $$ text "extern StgPtr "
    
    259
    +        $$ text "extern StgClosure "
    
    260 260
                <> (pprCLabel platform $ mkClosureLabel (idName n) (idCafInfo n)) <> semi
    
    261 261
             $$ text "hs_spt_insert" <> parens
    
    262 262
                  (hcat $ punctuate comma
    

  • compiler/ghc.cabal.in
    ... ... @@ -242,6 +242,7 @@ Library
    242 242
             GHC.Cmm.Dataflow.Label
    
    243 243
             GHC.Cmm.DebugBlock
    
    244 244
             GHC.Cmm.Expr
    
    245
    +        GHC.Cmm.GenerateDebugSymbolStub
    
    245 246
             GHC.Cmm.GenericOpt
    
    246 247
             GHC.Cmm.Graph
    
    247 248
             GHC.Cmm.Info
    

  • configure.ac
    ... ... @@ -876,9 +876,6 @@ AC_SUBST([UseLibm])
    876 876
     TargetHasLibm=$UseLibm
    
    877 877
     AC_SUBST(TargetHasLibm)
    
    878 878
     
    
    879
    -FP_BFD_FLAG
    
    880
    -AC_SUBST([UseLibbfd])
    
    881
    -
    
    882 879
     dnl ################################################################
    
    883 880
     dnl Check for libraries
    
    884 881
     dnl ################################################################
    

  • hadrian/cfg/system.config.in
    ... ... @@ -120,7 +120,6 @@ use-lib-numa = @UseLibNuma@
    120 120
     use-lib-m         = @UseLibm@
    
    121 121
     use-lib-rt        = @UseLibrt@
    
    122 122
     use-lib-dl        = @UseLibdl@
    
    123
    -use-lib-bfd       = @UseLibbfd@
    
    124 123
     use-lib-pthread   = @UseLibpthread@
    
    125 124
     need-libatomic    = @NeedLibatomic@
    
    126 125
     
    

  • hadrian/src/Oracles/Flag.hs
    ... ... @@ -36,7 +36,6 @@ data Flag = CrossCompiling
    36 36
               | UseLibm
    
    37 37
               | UseLibrt
    
    38 38
               | UseLibdl
    
    39
    -          | UseLibbfd
    
    40 39
               | UseLibpthread
    
    41 40
               | NeedLibatomic
    
    42 41
               | UseGhcToolchain
    
    ... ... @@ -60,7 +59,6 @@ flag f = do
    60 59
                 UseLibm              -> "use-lib-m"
    
    61 60
                 UseLibrt             -> "use-lib-rt"
    
    62 61
                 UseLibdl             -> "use-lib-dl"
    
    63
    -            UseLibbfd            -> "use-lib-bfd"
    
    64 62
                 UseLibpthread        -> "use-lib-pthread"
    
    65 63
                 NeedLibatomic        -> "need-libatomic"
    
    66 64
                 UseGhcToolchain      -> "use-ghc-toolchain"
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -442,7 +442,6 @@ rtsPackageArgs = package rts ? do
    442 442
               , useSystemFfi                    `cabalFlag` "use-system-libffi"
    
    443 443
               , useLibffiForAdjustors           `cabalFlag` "libffi-adjustors"
    
    444 444
               , flag UseLibpthread              `cabalFlag` "need-pthread"
    
    445
    -          , flag UseLibbfd                  `cabalFlag` "libbfd"
    
    446 445
               , flag NeedLibatomic              `cabalFlag` "need-atomic"
    
    447 446
               , flag UseLibdw                   `cabalFlag` "libdw"
    
    448 447
               , flag UseLibnuma                 `cabalFlag` "libnuma"
    

  • m4/fp_bfd_support.m4 deleted
    1
    -# FP_BFD_SUPPORT()
    
    2
    -# ----------------------
    
    3
    -# Whether to use libbfd for debugging RTS
    
    4
    -#
    
    5
    -# Sets:
    
    6
    -#   UseLibbfd: [YES|NO]
    
    7
    -AC_DEFUN([FP_BFD_FLAG], [
    
    8
    -  UseLibbfd=NO
    
    9
    -  AC_ARG_ENABLE(bfd-debug,
    
    10
    -    [AS_HELP_STRING([--enable-bfd-debug],
    
    11
    -          [Enable symbol resolution for -debug rts ('+RTS -Di') via binutils' libbfd [default=no]])],
    
    12
    -    [UseLibbfd=YES],
    
    13
    -    [UseLibbfd=NO])
    
    14
    -])
    
    15
    -
    
    16
    -# FP_WHEN_ENABLED_BFD
    
    17
    -# ----------------------
    
    18
    -# Checks for libraries in the default way, which will define various
    
    19
    -# `HAVE_*` macros.
    
    20
    -AC_DEFUN([FP_WHEN_ENABLED_BFD], [
    
    21
    -  # don't pollute general LIBS environment
    
    22
    -  save_LIBS="$LIBS"
    
    23
    -  AC_CHECK_HEADERS([bfd.h])
    
    24
    -  dnl ** check whether this machine has BFD and libiberty installed (used for debugging)
    
    25
    -  dnl    the order of these tests matters: bfd needs libiberty
    
    26
    -  AC_CHECK_LIB(iberty, xmalloc)
    
    27
    -  dnl 'bfd_init' is a rare non-macro in libbfd
    
    28
    -  AC_CHECK_LIB(bfd,    bfd_init)
    
    29
    -
    
    30
    -  AC_LINK_IFELSE(
    
    31
    -    [AC_LANG_PROGRAM(
    
    32
    -      [[#include <bfd.h>]],
    
    33
    -      [[
    
    34
    -        /* mimic our rts/Printer.c */
    
    35
    -        bfd* abfd;
    
    36
    -        const char * name;
    
    37
    -        char **matching;
    
    38
    -
    
    39
    -        name = "some.executable";
    
    40
    -        bfd_init();
    
    41
    -        abfd = bfd_openr(name, "default");
    
    42
    -        bfd_check_format_matches (abfd, bfd_object, &matching);
    
    43
    -        {
    
    44
    -            long storage_needed;
    
    45
    -            storage_needed = bfd_get_symtab_upper_bound (abfd);
    
    46
    -        }
    
    47
    -        {
    
    48
    -            asymbol **symbol_table;
    
    49
    -            long number_of_symbols;
    
    50
    -            symbol_info info;
    
    51
    -
    
    52
    -            number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
    
    53
    -            bfd_get_symbol_info(abfd,symbol_table[0],&info);
    
    54
    -        }
    
    55
    -      ]])],
    
    56
    -    [], dnl bfd seems to work
    
    57
    -    [AC_MSG_ERROR([can't use 'bfd' library])])
    
    58
    -  LIBS="$save_LIBS"
    
    59
    -])

  • rts/Printer.c
    ... ... @@ -43,13 +43,20 @@ static void printStdObjPayload( const StgClosure *obj );
    43 43
     void printPtr( StgPtr p )
    
    44 44
     {
    
    45 45
         const char *raw;
    
    46
    -    raw = lookupGHCName(p);
    
    46
    +    raw = lookupDebugSymbol(p);
    
    47 47
         if (raw != NULL) {
    
    48
    -        debugBelch("<%s>", raw);
    
    49
    -        debugBelch("[%p]", p);
    
    50
    -    } else {
    
    51
    -        debugBelch("%p", p);
    
    48
    +        debugBelch("<%s>[%p]", raw, p);
    
    49
    +        return;
    
    52 50
         }
    
    51
    +
    
    52
    +    StgPtr p0 = (StgPtr)UNTAG_CLOSURE((StgClosure *)p);
    
    53
    +    raw = lookupDebugSymbol(p0);
    
    54
    +    if (raw != NULL) {
    
    55
    +        debugBelch("<%s>[%p+%td]", raw, p0, p - p0);
    
    56
    +        return;
    
    57
    +    }
    
    58
    +
    
    59
    +    debugBelch("%p", p);
    
    53 60
     }
    
    54 61
     
    
    55 62
     void printObj( StgClosure *obj )
    
    ... ... @@ -853,129 +860,6 @@ void printLargeAndPinnedObjects(void)
    853 860
      * Uses symbol table in (unstripped executable)
    
    854 861
      * ------------------------------------------------------------------------*/
    
    855 862
     
    
    856
    -/* --------------------------------------------------------------------------
    
    857
    - * Simple lookup table
    
    858
    - * address -> function name
    
    859
    - * ------------------------------------------------------------------------*/
    
    860
    -
    
    861
    -static HashTable * add_to_fname_table = NULL;
    
    862
    -
    
    863
    -const char *lookupGHCName( void *addr )
    
    864
    -{
    
    865
    -    if (add_to_fname_table == NULL)
    
    866
    -        return NULL;
    
    867
    -
    
    868
    -    return lookupHashTable(add_to_fname_table, (StgWord)addr);
    
    869
    -}
    
    870
    -
    
    871
    -/* --------------------------------------------------------------------------
    
    872
    - * Symbol table loading
    
    873
    - * ------------------------------------------------------------------------*/
    
    874
    -
    
    875
    -/* Causing linking trouble on Win32 plats, so I'm
    
    876
    -   disabling this for now.
    
    877
    -*/
    
    878
    -#if defined(USING_LIBBFD)
    
    879
    -#    define PACKAGE 1
    
    880
    -#    define PACKAGE_VERSION 1
    
    881
    -/* Those PACKAGE_* defines are workarounds for bfd:
    
    882
    - *     https://sourceware.org/bugzilla/show_bug.cgi?id=14243
    
    883
    - * ghc's build system filter PACKAGE_* values out specifically to avoid clashes
    
    884
    - * with user's autoconf-based Cabal packages.
    
    885
    - * It's a shame <bfd.h> checks for unrelated fields instead of actually used
    
    886
    - * macros.
    
    887
    - */
    
    888
    -#    include <bfd.h>
    
    889
    -
    
    890
    -/* Fairly ad-hoc piece of code that seems to filter out a lot of
    
    891
    - * rubbish like the obj-splitting symbols
    
    892
    - */
    
    893
    -
    
    894
    -static bool isReal( flagword flags STG_UNUSED, const char *name )
    
    895
    -{
    
    896
    -#if 0
    
    897
    -    /* ToDo: make this work on BFD */
    
    898
    -    int tp = type & N_TYPE;
    
    899
    -    if (tp == N_TEXT || tp == N_DATA) {
    
    900
    -        return (name[0] == '_' && name[1] != '_');
    
    901
    -    } else {
    
    902
    -        return false;
    
    903
    -    }
    
    904
    -#else
    
    905
    -    if (*name == '\0'  ||
    
    906
    -        (name[0] == 'g' && name[1] == 'c' && name[2] == 'c') ||
    
    907
    -        (name[0] == 'c' && name[1] == 'c' && name[2] == '.')) {
    
    908
    -        return false;
    
    909
    -    }
    
    910
    -    return true;
    
    911
    -#endif
    
    912
    -}
    
    913
    -
    
    914
    -extern void DEBUG_LoadSymbols( const char *name )
    
    915
    -{
    
    916
    -    bfd* abfd;
    
    917
    -    char **matching;
    
    918
    -
    
    919
    -    bfd_init();
    
    920
    -    abfd = bfd_openr(name, "default");
    
    921
    -    if (abfd == NULL) {
    
    922
    -        barf("can't open executable %s to get symbol table", name);
    
    923
    -    }
    
    924
    -    if (!bfd_check_format_matches (abfd, bfd_object, &matching)) {
    
    925
    -        barf("mismatch");
    
    926
    -    }
    
    927
    -
    
    928
    -    {
    
    929
    -        long storage_needed;
    
    930
    -        asymbol **symbol_table;
    
    931
    -        long number_of_symbols;
    
    932
    -        long num_real_syms = 0;
    
    933
    -        long i;
    
    934
    -
    
    935
    -        storage_needed = bfd_get_symtab_upper_bound (abfd);
    
    936
    -
    
    937
    -        if (storage_needed < 0) {
    
    938
    -            barf("can't read symbol table");
    
    939
    -        }
    
    940
    -        symbol_table = (asymbol **) stgMallocBytes(storage_needed,"DEBUG_LoadSymbols");
    
    941
    -
    
    942
    -        number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table);
    
    943
    -
    
    944
    -        if (number_of_symbols < 0) {
    
    945
    -            barf("can't canonicalise symbol table");
    
    946
    -        }
    
    947
    -
    
    948
    -        if (add_to_fname_table == NULL)
    
    949
    -            add_to_fname_table = allocHashTable();
    
    950
    -
    
    951
    -        for( i = 0; i != number_of_symbols; ++i ) {
    
    952
    -            symbol_info info;
    
    953
    -            bfd_get_symbol_info(abfd,symbol_table[i],&info);
    
    954
    -            if (isReal(info.type, info.name)) {
    
    955
    -                insertHashTable(add_to_fname_table,
    
    956
    -                                info.value, (void*)info.name);
    
    957
    -                num_real_syms += 1;
    
    958
    -            }
    
    959
    -        }
    
    960
    -
    
    961
    -        IF_DEBUG(interpreter,
    
    962
    -                 debugBelch("Loaded %ld symbols. Of which %ld are real symbols\n",
    
    963
    -                         number_of_symbols, num_real_syms)
    
    964
    -                 );
    
    965
    -
    
    966
    -        stgFree(symbol_table);
    
    967
    -    }
    
    968
    -}
    
    969
    -
    
    970
    -#else /* USING_LIBBFD */
    
    971
    -
    
    972
    -extern void DEBUG_LoadSymbols( const char *name STG_UNUSED )
    
    973
    -{
    
    974
    -  /* nothing, yet */
    
    975
    -}
    
    976
    -
    
    977
    -#endif /* USING_LIBBFD */
    
    978
    -
    
    979 863
     void findPtr(P_ p, int);                /* keep gcc -Wall happy */
    
    980 864
     
    
    981 865
     int searched = 0;
    
    ... ... @@ -1080,6 +964,31 @@ void printObj( StgClosure *obj )
    1080 964
     
    
    1081 965
     #endif /* DEBUG */
    
    1082 966
     
    
    967
    +/* --------------------------------------------------------------------------
    
    968
    + * Simple lookup table
    
    969
    + * address -> function name
    
    970
    + * ------------------------------------------------------------------------*/
    
    971
    +
    
    972
    +static HashTable * add_to_fname_table = NULL;
    
    973
    +
    
    974
    +void registerDebugSymbol( const DebugSymbolEntry entries[], int len ) {
    
    975
    +    if (add_to_fname_table == NULL) {
    
    976
    +        add_to_fname_table = allocHashTable();
    
    977
    +    }
    
    978
    +
    
    979
    +    for (int i = 0; i < len; ++i) {
    
    980
    +        insertHashTable(add_to_fname_table, (StgWord)entries[i].addr, entries[i].sym);
    
    981
    +    }
    
    982
    +}
    
    983
    +
    
    984
    +const char *lookupDebugSymbol( void *addr )
    
    985
    +{
    
    986
    +    if (add_to_fname_table == NULL)
    
    987
    +        return NULL;
    
    988
    +
    
    989
    +    return lookupHashTable(add_to_fname_table, (StgWord)addr);
    
    990
    +}
    
    991
    +
    
    1083 992
     /* -----------------------------------------------------------------------------
    
    1084 993
        Closure types
    
    1085 994
     
    

  • rts/Printer.h
    ... ... @@ -30,11 +30,9 @@ extern void printStaticObjects ( StgClosure *obj );
    30 30
     extern void        printWeakLists ( void );
    
    31 31
     extern void        printLargeAndPinnedObjects ( void );
    
    32 32
     
    
    33
    -extern void DEBUG_LoadSymbols( const char *name );
    
    34
    -
    
    35
    -extern const char *lookupGHCName( void *addr );
    
    36
    -
    
    37 33
     extern const char *what_next_strs[];
    
    38 34
     #endif
    
    39 35
     
    
    36
    +extern const char *lookupDebugSymbol( void *addr );
    
    37
    +
    
    40 38
     #include "EndPrivate.h"

  • rts/RtsStartup.c
    ... ... @@ -15,7 +15,6 @@
    15 15
     #include "RtsFlags.h"
    
    16 16
     #include "RtsUtils.h"
    
    17 17
     #include "Prelude.h"
    
    18
    -#include "Printer.h"    /* DEBUG_LoadSymbols */
    
    19 18
     #include "Schedule.h"   /* initScheduler */
    
    20 19
     #include "Stats.h"      /* initStats */
    
    21 20
     #include "STM.h"        /* initSTM */
    
    ... ... @@ -326,11 +325,6 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config)
    326 325
         } else {
    
    327 326
             setFullProgArgv(*argc,*argv);
    
    328 327
             setupRtsFlags(argc, *argv, rts_config);
    
    329
    -
    
    330
    -#if defined(DEBUG)
    
    331
    -        /* load debugging symbols for current binary */
    
    332
    -        DEBUG_LoadSymbols((*argv)[0]);
    
    333
    -#endif /* DEBUG */
    
    334 328
         }
    
    335 329
     
    
    336 330
         /* Based on the RTS flags, decide which I/O manager to use. */
    

  • rts/configure.ac
    ... ... @@ -171,8 +171,6 @@ AS_IF(
    171 171
       [test "$CABAL_FLAG_libm" = 1],
    
    172 172
       [AC_DEFINE([HAVE_LIBM], [1], [Define to 1 if you need to link with libm])])
    
    173 173
     
    
    174
    -AS_IF([test "$CABAL_FLAG_libbfd" = 1], [FP_WHEN_ENABLED_BFD])
    
    175
    -
    
    176 174
     dnl ################################################################
    
    177 175
     dnl Check for libraries
    
    178 176
     dnl ################################################################
    

  • rts/include/Rts.h
    ... ... @@ -283,6 +283,7 @@ void _warnFail(const char *filename, unsigned int linenum);
    283 283
     #include "rts/StaticPtrTable.h"
    
    284 284
     #include "rts/Libdw.h"
    
    285 285
     #include "rts/LibdwPool.h"
    
    286
    +#include "rts/Debug.h"
    
    286 287
     
    
    287 288
     /* Misc stuff without a home */
    
    288 289
     DLL_IMPORT_RTS extern char **prog_argv; /* so we can get at these from Haskell */
    

  • rts/include/rts/Config.h
    ... ... @@ -19,13 +19,6 @@
    19 19
     #error TICKY_TICKY is incompatible with THREADED_RTS
    
    20 20
     #endif
    
    21 21
     
    
    22
    -/*
    
    23
    - * Whether the runtime system will use libbfd for debugging purposes.
    
    24
    - */
    
    25
    -#if defined(DEBUG) && defined(HAVE_BFD_H) && defined(HAVE_LIBBFD) && !defined(_WIN32)
    
    26
    -#define USING_LIBBFD 1
    
    27
    -#endif
    
    28
    -
    
    29 22
     /*
    
    30 23
      * We previously only offer the eventlog in a subset of RTS ways; we now
    
    31 24
      * enable it unconditionally to simplify packaging. See #18948.
    
    ... ... @@ -101,4 +94,3 @@ code.
    101 94
     #else
    
    102 95
     #define CACHELINE_SIZE 64
    
    103 96
     #endif
    104
    -

  • rts/include/rts/Debug.h
    1
    +/* -----------------------------------------------------------------------------
    
    2
    + *
    
    3
    + * (c) The GHC Team, 2017-2025
    
    4
    + *
    
    5
    + * Debug API
    
    6
    + *
    
    7
    + * Do not #include this file directly: #include "Rts.h" instead.
    
    8
    + *
    
    9
    + * To understand the structure of the RTS headers, see the wiki:
    
    10
    + *   https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes
    
    11
    + *
    
    12
    + * -------------------------------------------------------------------------- */
    
    13
    +
    
    14
    +#pragma once
    
    15
    +
    
    16
    +typedef struct { void *addr; const char *sym; } DebugSymbolEntry;
    
    17
    +
    
    18
    +void registerDebugSymbol( const DebugSymbolEntry entries[], int len );

  • rts/rts.cabal
    ... ... @@ -46,9 +46,6 @@ flag libffi-adjustors
    46 46
     flag need-pthread
    
    47 47
       default: False
    
    48 48
       manual: True
    
    49
    -flag libbfd
    
    50
    -  default: False
    
    51
    -  manual: True
    
    52 49
     flag need-atomic
    
    53 50
       default: False
    
    54 51
       manual: True
    
    ... ... @@ -250,9 +247,6 @@ library
    250 247
           if flag(need-atomic)
    
    251 248
              -- for sub-word-sized atomic operations (#19119)
    
    252 249
              extra-libraries: atomic
    
    253
    -      if flag(libbfd)
    
    254
    -         -- for debugging
    
    255
    -         extra-libraries: bfd iberty
    
    256 250
           if flag(libdw)
    
    257 251
              -- for backtraces
    
    258 252
              extra-libraries: elf dw
    
    ... ... @@ -286,6 +280,7 @@ library
    286 280
                             rts/Bytecodes.h
    
    287 281
                             rts/Config.h
    
    288 282
                             rts/Constants.h
    
    283
    +                        rts/Debug.h
    
    289 284
                             rts/EventLogFormat.h
    
    290 285
                             rts/EventLogWriter.h
    
    291 286
                             rts/FileLock.h