dwarf-0.23: Parser for DWARF debug format.

Data.Dwarf

Description

Parses the DWARF 2 and DWARF 3 specifications at http:www.dwarfstd.org given the debug sections in ByteString form.

Synopsis

Documentation

parseDwarfInfoSource

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.

infoCompileUnitSource

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.

parseDwarfFrameSource

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_ate :: Num a => a -> DW_ATESource

dw_ds :: Num a => a -> DW_DSSource

dw_end :: Num a => a -> DW_ENDSource

dw_vis :: Num a => a -> DW_VISSource

dw_inl :: Num a => a -> DW_INLSource

dw_cc :: Num a => a -> DW_CCSource

dw_ord :: Num a => a -> DW_ORDSource

dw_dsc :: Num a => a -> DW_DSCSource

(!?) :: 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

littleEndian :: Bool

True for little endian encoding.

dwarf64 :: Bool

True for 64-bit DWARF encoding.

target64 :: Bool

True for 64-bit pointers on target machine.

largestOffset :: Word64

Largest permissible file offset.

largestTargetAddress :: Word64

Largest permissible target address.

getWord16 :: Get Word16

Action for reading a 16-bit word.

getWord32 :: Get Word32

Action for reading a 32-bit word.

getWord64 :: Get Word64

Action for reading a 64-bit word.

getDwarfOffset :: Get Word64

Action for reading a offset for the DWARF file.

getDwarfTargetAddress :: Get Word64

Action for reading a pointer for the target machine.

data DIE Source

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

dieId :: Word64

Unique identifier for this entry.

dieParent :: Maybe Word64

Unique identifier of this entry's parent.

dieChildren :: [Word64]

Unique identifiers of this entry's children.

dieSiblingLeft :: Maybe Word64

Unique identifier of the left sibling in the DIE tree, if one exists.

dieSiblingRight :: Maybe Word64

Unique identifier of the right sibling in the DIE tree, if one exists.

dieTag :: DW_TAG

Type tag.

dieAttributes :: [(DW_AT, DW_ATVAL)]

Attribute tag and value pairs.

dieReader :: DwarfReader

Decoder used to decode this entry. May be needed to further parse attribute values.

Instances

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

data DW_OP Source

Constructors

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 

Instances

data DW_AT Source

Constructors

DW_AT_sibling

reference

DW_AT_location

block, loclistptr

DW_AT_name

string

DW_AT_ordering

constant

DW_AT_byte_size

block, constant, reference

DW_AT_bit_offset

block, constant, reference

DW_AT_bit_size

block, constant, reference

DW_AT_stmt_list

lineptr

DW_AT_low_pc

address

DW_AT_high_pc

address

DW_AT_language

constant

DW_AT_discr

reference

DW_AT_discr_value

constant

DW_AT_visibility

constant

DW_AT_import

reference

DW_AT_string_length

block, loclistptr

DW_AT_common_reference

reference

DW_AT_comp_dir

string

DW_AT_const_value

block, constant, string

DW_AT_containing_type

reference

DW_AT_default_value

reference

DW_AT_inline

constant

DW_AT_is_optional

flag

DW_AT_lower_bound

block, constant, reference

DW_AT_producer

string

DW_AT_prototyped

flag

DW_AT_return_addr

block, loclistptr

DW_AT_start_scope

constant

DW_AT_bit_stride

constant

DW_AT_upper_bound

block, constant, reference

DW_AT_abstract_origin

reference

DW_AT_accessibility

constant

DW_AT_address_class

constant

DW_AT_artificial

flag

DW_AT_base_types

reference

DW_AT_calling_convention

constant

DW_AT_count

block, constant, reference

DW_AT_data_member_location

block, constant, loclistptr

DW_AT_decl_column

constant

DW_AT_decl_file

constant

DW_AT_decl_line

constant

DW_AT_declaration

flag

DW_AT_discr_list

block

DW_AT_encoding

constant

DW_AT_external

flag

DW_AT_frame_base

block, loclistptr

DW_AT_friend

reference

DW_AT_identifier_case

constant

DW_AT_macro_info

macptr

DW_AT_namelist_item

block

DW_AT_priority

reference

DW_AT_segment

block, loclistptr

DW_AT_specification

reference

DW_AT_static_link

block, loclistptr

DW_AT_type

reference

DW_AT_use_location

block, loclistptr

DW_AT_variable_parameter

flag

DW_AT_virtuality

constant

DW_AT_vtable_elem_location

block, loclistptr

DW_AT_allocated

block, constant, reference

DW_AT_associated

block, constant, reference

DW_AT_data_location

block

DW_AT_byte_stride

block, constant, reference

DW_AT_entry_pc

address

DW_AT_use_UTF8

flag

DW_AT_extension

reference

DW_AT_ranges

rangelistptr

DW_AT_trampoline

address, flag, reference, string

DW_AT_call_column

constant

DW_AT_call_file

constant

DW_AT_call_line

constant

DW_AT_description

string

DW_AT_binary_scale

constant

DW_AT_decimal_scale

constant

DW_AT_small

reference

DW_AT_decimal_sign

constant

DW_AT_digit_count

constant

DW_AT_picture_string

string

DW_AT_mutable

flag

DW_AT_threads_scaled

flag

DW_AT_explicit

flag

DW_AT_object_pointer

reference

DW_AT_endianity

constant

DW_AT_elemental

flag

DW_AT_pure

flag

DW_AT_recursive

flag

DW_AT_user Word64

user extension

Instances

data DW_DSC Source

Constructors

DW_DSC_label 
DW_DSC_range 

Instances