Data.Dwarf
Description
Parses the DWARF 2 and DWARF 3 specifications at http:www.dwarfstd.org given the debug sections in ByteString form.
- parseDwarfInfo :: Bool -> ByteString -> ByteString -> ByteString -> Map Word64 DIE
- infoCompileUnit :: ByteString -> Word64 -> Word64
- parseDwarfAranges :: Bool -> Bool -> ByteString -> [([(Word64, Word64)], Word64)]
- parseDwarfPubnames :: Bool -> Bool -> ByteString -> Map String [Word64]
- parseDwarfPubtypes :: Bool -> Bool -> ByteString -> Map String [Word64]
- parseDwarfMacInfo :: ByteString -> [DW_MACINFO]
- parseDwarfRanges :: DwarfReader -> ByteString -> [Either Word64 (Word64, Word64)]
- parseDwarfLoc :: DwarfReader -> ByteString -> [Either Word64 (Word64, Word64, ByteString)]
- parseDwarfLine :: Bool -> Bool -> ByteString -> ([String], [DW_LNE])
- parseDwarfFrame :: Bool -> Bool -> ByteString -> [DW_CIEFDE]
- parseDW_OP :: DwarfReader -> ByteString -> DW_OP
- dw_ate :: Num a => a -> DW_ATE
- dw_ds :: Num a => a -> DW_DS
- dw_end :: Num a => a -> DW_END
- dw_access :: Num a => a -> DW_ACCESS
- dw_vis :: Num a => a -> DW_VIS
- dw_virtuality :: Num a => a -> DW_VIRTUALITY
- dw_lang :: Num a => a -> DW_LANG
- dw_inl :: Num a => a -> DW_INL
- dw_cc :: Num a => a -> DW_CC
- dw_ord :: Num a => a -> DW_ORD
- dw_dsc :: Num a => a -> DW_DSC
- (!?) :: DIE -> DW_AT -> [DW_ATVAL]
- data DwarfReader = DwarfReader {}
- data DIE = DIE {
- dieId :: Word64
- dieParent :: Maybe Word64
- dieChildren :: [Word64]
- dieSiblingLeft :: Maybe Word64
- dieSiblingRight :: Maybe Word64
- dieTag :: DW_TAG
- dieAttributes :: [(DW_AT, DW_ATVAL)]
- dieReader :: DwarfReader
- data DW_CFA
- = DW_CFA_advance_loc Word8
- | DW_CFA_offset Word8 Word64
- | DW_CFA_restore Word8
- | DW_CFA_nop
- | DW_CFA_set_loc Word64
- | DW_CFA_advance_loc1 Word8
- | DW_CFA_advance_loc2 Word16
- | DW_CFA_advance_loc4 Word32
- | DW_CFA_offset_extended Word64 Word64
- | DW_CFA_restore_extended Word64
- | DW_CFA_undefined Word64
- | DW_CFA_same_value Word64
- | DW_CFA_register Word64 Word64
- | DW_CFA_remember_state
- | DW_CFA_restore_state
- | DW_CFA_def_cfa Word64 Word64
- | DW_CFA_def_cfa_register Word64
- | DW_CFA_def_cfa_offset Word64
- | DW_CFA_def_cfa_expression ByteString
- | DW_CFA_expression Word64 ByteString
- | DW_CFA_offset_extended_sf Word64 Int64
- | DW_CFA_def_cfa_sf Word64 Int64
- | DW_CFA_def_cfa_offset_sf Int64
- | DW_CFA_val_offset Word64 Word64
- | DW_CFA_val_offset_sf Word64 Int64
- | DW_CFA_val_expression Word64 ByteString
- data DW_MACINFO
- data DW_CIEFDE
- data DW_OP
- = DW_OP_addr Word64
- | DW_OP_deref
- | DW_OP_const1u Word8
- | DW_OP_const1s Int8
- | DW_OP_const2u Word16
- | DW_OP_const2s Int16
- | DW_OP_const4u Word32
- | DW_OP_const4s Int32
- | DW_OP_const8u Word64
- | DW_OP_const8s Int64
- | DW_OP_constu Word64
- | DW_OP_consts Int64
- | DW_OP_dup
- | DW_OP_drop
- | DW_OP_over
- | DW_OP_pick Word8
- | DW_OP_swap
- | DW_OP_rot
- | DW_OP_xderef
- | DW_OP_abs
- | DW_OP_and
- | DW_OP_div
- | DW_OP_minus
- | DW_OP_mod
- | DW_OP_mul
- | DW_OP_neg
- | DW_OP_not
- | DW_OP_or
- | DW_OP_plus
- | DW_OP_plus_uconst Word64
- | DW_OP_shl
- | DW_OP_shr
- | DW_OP_shra
- | DW_OP_xor
- | DW_OP_skip Int16
- | DW_OP_bra Int16
- | DW_OP_eq
- | DW_OP_ge
- | DW_OP_gt
- | DW_OP_le
- | DW_OP_lt
- | DW_OP_ne
- | DW_OP_lit0
- | DW_OP_lit1
- | DW_OP_lit2
- | DW_OP_lit3
- | DW_OP_lit4
- | DW_OP_lit5
- | DW_OP_lit6
- | DW_OP_lit7
- | DW_OP_lit8
- | DW_OP_lit9
- | DW_OP_lit10
- | DW_OP_lit11
- | DW_OP_lit12
- | DW_OP_lit13
- | DW_OP_lit14
- | DW_OP_lit15
- | DW_OP_lit16
- | DW_OP_lit17
- | DW_OP_lit18
- | DW_OP_lit19
- | DW_OP_lit20
- | DW_OP_lit21
- | DW_OP_lit22
- | DW_OP_lit23
- | DW_OP_lit24
- | DW_OP_lit25
- | DW_OP_lit26
- | DW_OP_lit27
- | DW_OP_lit28
- | DW_OP_lit29
- | DW_OP_lit30
- | DW_OP_lit31
- | DW_OP_reg0
- | DW_OP_reg1
- | DW_OP_reg2
- | DW_OP_reg3
- | DW_OP_reg4
- | DW_OP_reg5
- | DW_OP_reg6
- | DW_OP_reg7
- | DW_OP_reg8
- | DW_OP_reg9
- | DW_OP_reg10
- | DW_OP_reg11
- | DW_OP_reg12
- | DW_OP_reg13
- | DW_OP_reg14
- | DW_OP_reg15
- | DW_OP_reg16
- | DW_OP_reg17
- | DW_OP_reg18
- | DW_OP_reg19
- | DW_OP_reg20
- | DW_OP_reg21
- | DW_OP_reg22
- | DW_OP_reg23
- | DW_OP_reg24
- | DW_OP_reg25
- | DW_OP_reg26
- | DW_OP_reg27
- | DW_OP_reg28
- | DW_OP_reg29
- | DW_OP_reg30
- | DW_OP_reg31
- | DW_OP_breg0 Int64
- | DW_OP_breg1 Int64
- | DW_OP_breg2 Int64
- | DW_OP_breg3 Int64
- | DW_OP_breg4 Int64
- | DW_OP_breg5 Int64
- | DW_OP_breg6 Int64
- | DW_OP_breg7 Int64
- | DW_OP_breg8 Int64
- | DW_OP_breg9 Int64
- | DW_OP_breg10 Int64
- | DW_OP_breg11 Int64
- | DW_OP_breg12 Int64
- | DW_OP_breg13 Int64
- | DW_OP_breg14 Int64
- | DW_OP_breg15 Int64
- | DW_OP_breg16 Int64
- | DW_OP_breg17 Int64
- | DW_OP_breg18 Int64
- | DW_OP_breg19 Int64
- | DW_OP_breg20 Int64
- | DW_OP_breg21 Int64
- | DW_OP_breg22 Int64
- | DW_OP_breg23 Int64
- | DW_OP_breg24 Int64
- | DW_OP_breg25 Int64
- | DW_OP_breg26 Int64
- | DW_OP_breg27 Int64
- | DW_OP_breg28 Int64
- | DW_OP_breg29 Int64
- | DW_OP_breg30 Int64
- | DW_OP_breg31 Int64
- | DW_OP_regx Word64
- | DW_OP_fbreg Int64
- | DW_OP_bregx Word64 Int64
- | DW_OP_piece Word64
- | DW_OP_deref_size Word8
- | DW_OP_xderef_size Word8
- | DW_OP_nop
- | DW_OP_push_object_address
- | DW_OP_call2 Word16
- | DW_OP_call4 Word32
- | DW_OP_call_ref Word64
- | DW_OP_form_tls_address
- | DW_OP_call_frame_cfa
- | DW_OP_bit_piece Word64 Word64
- data DW_TAG
- = DW_TAG_array_type
- | DW_TAG_class_type
- | DW_TAG_entry_point
- | DW_TAG_enumeration_type
- | DW_TAG_formal_parameter
- | DW_TAG_imported_declaration
- | DW_TAG_label
- | DW_TAG_lexical_block
- | DW_TAG_member
- | DW_TAG_pointer_type
- | DW_TAG_reference_type
- | DW_TAG_compile_unit
- | DW_TAG_string_type
- | DW_TAG_structure_type
- | DW_TAG_subroutine_type
- | DW_TAG_typedef
- | DW_TAG_union_type
- | DW_TAG_unspecified_parameters
- | DW_TAG_variant
- | DW_TAG_common_block
- | DW_TAG_common_inclusion
- | DW_TAG_inheritance
- | DW_TAG_inlined_subroutine
- | DW_TAG_module
- | DW_TAG_ptr_to_member_type
- | DW_TAG_set_type
- | DW_TAG_subrange_type
- | DW_TAG_with_stmt
- | DW_TAG_access_declaration
- | DW_TAG_base_type
- | DW_TAG_catch_block
- | DW_TAG_const_type
- | DW_TAG_constant
- | DW_TAG_enumerator
- | DW_TAG_file_type
- | DW_TAG_friend
- | DW_TAG_namelist
- | DW_TAG_namelist_item
- | DW_TAG_packed_type
- | DW_TAG_subprogram
- | DW_TAG_template_type_parameter
- | DW_TAG_template_value_parameter
- | DW_TAG_thrown_type
- | DW_TAG_try_block
- | DW_TAG_variant_part
- | DW_TAG_variable
- | DW_TAG_volatile_type
- | DW_TAG_dwarf_procedure
- | DW_TAG_restrict_type
- | DW_TAG_interface_type
- | DW_TAG_namespace
- | DW_TAG_imported_module
- | DW_TAG_unspecified_type
- | DW_TAG_partial_unit
- | DW_TAG_imported_unit
- | DW_TAG_condition
- | DW_TAG_shared_type
- data DW_AT
- = DW_AT_sibling
- | DW_AT_location
- | DW_AT_name
- | DW_AT_ordering
- | DW_AT_byte_size
- | DW_AT_bit_offset
- | DW_AT_bit_size
- | DW_AT_stmt_list
- | DW_AT_low_pc
- | DW_AT_high_pc
- | DW_AT_language
- | DW_AT_discr
- | DW_AT_discr_value
- | DW_AT_visibility
- | DW_AT_import
- | DW_AT_string_length
- | DW_AT_common_reference
- | DW_AT_comp_dir
- | DW_AT_const_value
- | DW_AT_containing_type
- | DW_AT_default_value
- | DW_AT_inline
- | DW_AT_is_optional
- | DW_AT_lower_bound
- | DW_AT_producer
- | DW_AT_prototyped
- | DW_AT_return_addr
- | DW_AT_start_scope
- | DW_AT_bit_stride
- | DW_AT_upper_bound
- | DW_AT_abstract_origin
- | DW_AT_accessibility
- | DW_AT_address_class
- | DW_AT_artificial
- | DW_AT_base_types
- | DW_AT_calling_convention
- | DW_AT_count
- | DW_AT_data_member_location
- | DW_AT_decl_column
- | DW_AT_decl_file
- | DW_AT_decl_line
- | DW_AT_declaration
- | DW_AT_discr_list
- | DW_AT_encoding
- | DW_AT_external
- | DW_AT_frame_base
- | DW_AT_friend
- | DW_AT_identifier_case
- | DW_AT_macro_info
- | DW_AT_namelist_item
- | DW_AT_priority
- | DW_AT_segment
- | DW_AT_specification
- | DW_AT_static_link
- | DW_AT_type
- | DW_AT_use_location
- | DW_AT_variable_parameter
- | DW_AT_virtuality
- | DW_AT_vtable_elem_location
- | DW_AT_allocated
- | DW_AT_associated
- | DW_AT_data_location
- | DW_AT_byte_stride
- | DW_AT_entry_pc
- | DW_AT_use_UTF8
- | DW_AT_extension
- | DW_AT_ranges
- | DW_AT_trampoline
- | DW_AT_call_column
- | DW_AT_call_file
- | DW_AT_call_line
- | DW_AT_description
- | DW_AT_binary_scale
- | DW_AT_decimal_scale
- | DW_AT_small
- | DW_AT_decimal_sign
- | DW_AT_digit_count
- | DW_AT_picture_string
- | DW_AT_mutable
- | DW_AT_threads_scaled
- | DW_AT_explicit
- | DW_AT_object_pointer
- | DW_AT_endianity
- | DW_AT_elemental
- | DW_AT_pure
- | DW_AT_recursive
- | DW_AT_user Word64
- data DW_ATVAL
- data DW_LNE = DW_LNE {
- lnmAddress :: Word64
- lnmFile :: Word64
- lnmLine :: Word64
- lnmColumn :: Word64
- lnmStatement :: Bool
- lnmBasicBlock :: Bool
- lnmEndSequence :: Bool
- lnmPrologueEnd :: Bool
- lnmEpilogueBegin :: Bool
- lnmISA :: Word64
- lnmFiles :: [(String, Word64, Word64, Word64)]
- data DW_ATE
- = DW_ATE_address
- | DW_ATE_boolean
- | DW_ATE_complex_float
- | DW_ATE_float
- | DW_ATE_signed
- | DW_ATE_signed_char
- | DW_ATE_unsigned
- | DW_ATE_unsigned_char
- | DW_ATE_imaginary_float
- | DW_ATE_packed_decimal
- | DW_ATE_numeric_string
- | DW_ATE_edited
- | DW_ATE_signed_fixed
- | DW_ATE_unsigned_fixed
- | DW_ATE_decimal_float
- data DW_DS
- data DW_END
- data DW_ACCESS
- data DW_VIS
- data DW_VIRTUALITY
- data DW_LANG
- = DW_LANG_C89
- | DW_LANG_C
- | DW_LANG_Ada83
- | DW_LANG_C_plus_plus
- | DW_LANG_Cobol74
- | DW_LANG_Cobol85
- | DW_LANG_Fortran77
- | DW_LANG_Fortran90
- | DW_LANG_Pascal83
- | DW_LANG_Modula2
- | DW_LANG_Java
- | DW_LANG_C99
- | DW_LANG_Ada95
- | DW_LANG_Fortran95
- | DW_LANG_PLI
- | DW_LANG_ObjC
- | DW_LANG_ObjC_plus_plus
- | DW_LANG_UPC
- | DW_LANG_D
- data DW_ID
- data DW_INL
- data DW_CC
- data DW_ORD
- data DW_DSC
Documentation
Arguments
:: Bool | True for little endian target addresses. False for big endian. |
-> ByteString | ByteString for the .debug_info section. |
-> ByteString | ByteString for the .debug_abbrev section. |
-> ByteString | ByteString for the .debug_str section. |
-> Map Word64 DIE | A map from the unique ids to their corresponding DWARF information entries. |
Parses the .debug_info section (as ByteString) using the .debug_abbrev and .debug_str sections.
Arguments
:: ByteString | Contents of .debug_info |
-> Word64 | Offset into .debug_info header |
-> Word64 | Offset of compile unit DIE. |
Returns compilation unit id given the header offset into .debug_info
parseDwarfAranges :: Bool -> Bool -> ByteString -> [([(Word64, Word64)], Word64)]Source
Parses the .debug_aranges section (as ByteString) into a map from an address range to a debug info id that indexes the DwarfInfo.
parseDwarfPubnames :: Bool -> Bool -> ByteString -> Map String [Word64]Source
Parses the .debug_pubnames section (as ByteString) into a map from a value name to a debug info id in the DwarfInfo.
parseDwarfPubtypes :: Bool -> Bool -> ByteString -> Map String [Word64]Source
Parses the .debug_pubtypes section (as ByteString) into a map from a type name to a debug info id in the DwarfInfo.
parseDwarfMacInfo :: ByteString -> [DW_MACINFO]Source
Retrieves the macro information for a compilation unit from a given substring of the .debug_macinfo section. The offset into the .debug_macinfo section is obtained from the DW_AT_macro_info attribute of a compilation unit DIE.
parseDwarfRanges :: DwarfReader -> ByteString -> [Either Word64 (Word64, Word64)]Source
Retrieves the non-contiguous address ranges for a compilation unit from a given substring of the .debug_ranges section. The offset into the .debug_ranges section is obtained from the DW_AT_ranges attribute of a compilation unit DIE. Left results are base address entries. Right results are address ranges.
parseDwarfLoc :: DwarfReader -> ByteString -> [Either Word64 (Word64, Word64, ByteString)]Source
Retrieves the location list expressions from a given substring of the .debug_loc section. The offset into the .debug_loc section is obtained from an attribute of class loclistptr for a given DIE. Left results are base address entries. Right results are address ranges and a location expression.
parseDwarfLine :: Bool -> Bool -> ByteString -> ([String], [DW_LNE])Source
Retrieves the line information for a DIE from a given substring of the .debug_line section. The offset into the .debug_line section is obtained from the DW_AT_stmt_list attribute of a DIE.
Arguments
:: Bool | True for little endian data. False for big endian. |
-> Bool | True for 64-bit target addresses. False of 32-bit target addresses. |
-> ByteString | ByteString for the .debug_frame section. |
-> [DW_CIEFDE] |
Parse the .debug_frame section into a list of DW_CIEFDE records.
parseDW_OP :: DwarfReader -> ByteString -> DW_OPSource
Parse a ByteString into a DWARF opcode. This will be needed for further decoding of DIE attributes.
dw_virtuality :: Num a => a -> DW_VIRTUALITYSource
(!?) :: DIE -> DW_AT -> [DW_ATVAL]Source
Utility function for retrieving the list of values for a specified attribute from a DWARF information entry.
data DwarfReader Source
Type containing functions and data needed for decoding DWARF information.
Constructors
DwarfReader | |
Fields
|
Instances
The dwarf information entries form a graph of nodes tagged with attributes. Please refer to the DWARF specification for semantics. Although it looks like a tree, there can be attributes which have adjacency information which will introduce cross-branch edges.
Constructors
DIE | |
Fields
|
Constructors
data DW_MACINFO Source
Constructors
DW_MACINFO_define Word64 String | Line number and defined symbol with definition |
DW_MACINFO_undef Word64 String | Line number and undefined symbol |
DW_MACINFO_start_file Word64 Word64 | Marks start of file with the line where the file was included from and a source file index |
DW_MACINFO_end_file | Marks end of file |
DW_MACINFO_vendor_ext Word64 String | Implementation defined |
Instances
Constructors
Constructors
Constructors
Constructors
DW_LNE | |
Fields
|
Constructors
DW_END_default | |
DW_END_big | |
DW_END_little |
Constructors
DW_ACCESS_public | |
DW_ACCESS_protected | |
DW_ACCESS_private |
Constructors
DW_VIS_local | |
DW_VIS_exported | |
DW_VIS_qualified |
data DW_VIRTUALITY Source
Instances