dwarf-el-0.2: Parser for DWARF debug format.

Safe HaskellNone

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

parseInfoSource

Arguments

:: Endianess 
-> Sections 
-> ([DIE], DIEMap)

The die list is of compilation unit dies

Parses the .debug_info section (as ByteString) using the .debug_abbrev and .debug_str sections.

data DieID Source

Instances

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 :: DieID

Unique identifier for this entry.

dieTag :: DW_TAG

Type tag.

dieAttributes :: [(DW_AT, DW_ATVAL)]

Attribute tag and value pairs.

dieChildren :: [DIE]
 
dieReader :: Reader

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

Instances

(!?) :: DIE -> DW_AT -> [DW_ATVAL]Source

Utility function for retrieving the list of values for a specified attribute from a DWARF information entry.

data DIERefs Source

Constructors

DIERefs 

Fields

dieRefsParent :: Maybe DieID

Unique identifier of this entry's parent.

dieRefsSiblingLeft :: Maybe DieID

Unique identifier of the left sibling

dieRefsSiblingRight :: Maybe DieID

Unique identifier of the right sibling

dieRefsDIE :: DIE
 

Instances

data Reader Source

Type containing functions and data needed for decoding DWARF information.

Constructors

Reader 

Fields

drDesr :: EndianSizeReader
 
drTarget64 :: TargetSize
 
drLargestTargetAddress :: Word64

Largest permissible target address.

drGetTargetAddress :: Get Word64

Action for reading a pointer for the target machine.

Instances

parseAranges :: Endianess -> TargetSize -> ByteString -> [([Range], CUOffset)]Source

Parses the .debug_aranges section (as ByteString) into a map from an address range to a DieID that indexes the Info.

parsePubnames :: Endianess -> TargetSize -> ByteString -> Map String [DieID]Source

Parses the .debug_pubnames section (as ByteString) into a map from a value name to a DieID

parsePubtypes :: Endianess -> TargetSize -> ByteString -> Map String [DieID]Source

Parses the .debug_pubtypes section (as ByteString) into a map from a type name to a DieID

data Range Source

Constructors

Range 

Fields

rangeBegin :: !Word64
 
rangeEnd :: !Word64
 

parseRanges :: Reader -> ByteString -> [Either RangeEnd Range]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.

parseLoc :: Reader -> ByteString -> [Either RangeEnd (Range, 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.

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

parseMacInfo :: 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.

parseFrameSource

Arguments

:: Endianess 
-> TargetSize 
-> ByteString

ByteString for the .debug_frame section.

-> [DW_CIEFDE] 

Parse the .debug_frame section into a list of DW_CIEFDE records.

parseDW_OP :: Reader -> ByteString -> DW_OPSource

Parse a ByteString into a DWARF opcode. This will be needed for further decoding of DIE attributes.

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_LANG)

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_return

flag

DW_AT_recursive

flag

DW_AT_user Word64

user extension

parseLNE :: Endianess -> TargetSize -> Word64 -> 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.