Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Macaw.Dwarf
Description
This defines data structures for parsing Dwarf debug information from binaries.
Synopsis
- data Endianness
- data Sections
- mkSections :: Applicative m => (ByteString -> m ByteString) -> m Sections
- data CUContext
- newtype CUOffset = CUOffset Word64
- firstCUContext :: Endianness -> Sections -> Maybe (Either String CUContext)
- nextCUContext :: CUContext -> Maybe (Either String CUContext)
- getCompileUnit :: CUContext -> (Either String CompileUnit, [String])
- dwarfCompileUnits :: Endianness -> Sections -> ([String], [CompileUnit])
- data CompileUnit
- cuSubprograms :: CompileUnit -> [Subprogram]
- lookupSubprogram :: SubprogramRef -> CompileUnit -> Maybe Subprogram
- dwarfGlobals :: [CompileUnit] -> [Variable]
- dwarfInfoFromElf :: forall (v :: Nat). Elf v -> ([String], [CompileUnit])
- data Variable
- varName :: Variable -> Name
- varType :: Variable -> Maybe TypeRef
- varOrigin :: Variable -> Maybe VariableRef
- data Subprogram = Subprogram {
- subName :: !Name
- subDescription :: !Description
- subLinkageName :: !ByteString
- subExternal :: !Bool
- subOrigin :: !(Maybe SubprogramRef)
- subIsDeclaration :: !Bool
- subEntryPC :: !(Maybe Word64)
- subArtificial :: !Bool
- subGNUAllTailCallSites :: !Bool
- subDeclLoc :: !DeclLoc
- subPrototyped :: !Bool
- subDef :: !(Maybe SubprogramDef)
- subVars :: !(Map VariableRef Variable)
- subParamMap :: !(Map VariableRef Variable)
- subUnspecifiedParams :: !Bool
- subRetType :: !(Maybe TypeRef)
- subNoreturn :: !Bool
- subTypeMap :: !(Map TypeRef AbsType)
- data SubprogramDef = SubprogramDef {}
- data SubprogramRef
- data VariableRef
- data Location
- data DeclLoc
- data TypeRef
- typeRefFileOffset :: TypeRef -> Word64
- type AbsType = (Either String TypeApp, [String])
- data TypeApp
- = BoolType
- | UnsignedIntType !Int
- | SignedIntType !Int
- | FloatType
- | DoubleType
- | LongDoubleType
- | UnsignedCharType
- | SignedCharType
- | ArrayType !TypeRef ![Subrange TypeRef]
- | PointerType !(Maybe Word64) !(Maybe TypeRef)
- | StructType !StructDecl
- | UnionType !UnionDecl
- | EnumType !EnumDecl
- | SubroutinePtrType !SubroutineTypeDecl
- | TypedefType !Typedef
- | TypeQualType !TypeQualAnn
- | SubroutineTypeF !SubroutineTypeDecl
- data StructDecl = StructDecl {
- structName :: !Name
- structDescription :: !Description
- structByteSize :: !Word64
- structLoc :: !DeclLoc
- structMembers :: ![Member]
- data UnionDecl = UnionDecl {
- unionName :: !Name
- unionDescription :: !Description
- unionByteSize :: !Word64
- unionLoc :: !DeclLoc
- unionMembers :: ![Member]
- data Member = Member {
- memberName :: !Name
- memberDescription :: !Description
- memberDeclLoc :: !DeclLoc
- memberLoc :: !(Maybe Word64)
- memberType :: !TypeRef
- memberArtificial :: !Bool
- memberByteSize :: !(Maybe Word64)
- memberBitOffset :: !(Maybe Word64)
- memberBitSize :: !(Maybe Word64)
- data EnumDecl = EnumDecl {
- enumDeclName :: !Name
- enumDeclDescription :: !Description
- enumDeclByteSize :: !Word64
- enumDeclLoc :: !DeclLoc
- enumDeclType :: !(Maybe TypeRef)
- enumDeclCases :: ![Enumerator]
- data Enumerator
- data SubroutineTypeDecl = SubroutineTypeDecl {
- fntypePrototyped :: !(Maybe Bool)
- fntypeFormals :: ![Variable]
- fntypeType :: !(Maybe TypeRef)
- data Subrange tp = Subrange {
- subrangeType :: tp
- subrangeUpperBound :: [DW_OP]
- data Typedef = Typedef {
- typedefName :: !Name
- typedefDescription :: !Description
- typedefLoc :: !DeclLoc
- typedefType :: !TypeRef
- data TypeQual
- data TypeQualAnn = TypeQualAnn {
- tqaTypeQual :: !TypeQual
- tqaName :: !Name
- tqaDescription :: !Description
- tqaDeclLoc :: !DeclLoc
- tqaAlign :: !Word64
- tqaType :: !(Maybe TypeRef)
- newtype Name = Name {}
- newtype Description = Description {}
- data DwarfExpr = DwarfExpr !Reader !ByteString
- data DieID
- data DW_OP
- = DW_OP_lit !Word8
- | DW_OP_addr !Word64
- | DW_OP_const1u !Word8
- | DW_OP_const2u !Word16
- | DW_OP_const4u !Word32
- | DW_OP_const8u !Word64
- | DW_OP_const1s Int8
- | DW_OP_const2s Int16
- | DW_OP_const4s Int32
- | DW_OP_const8s Int64
- | DW_OP_constu !Word64
- | DW_OP_consts !Int64
- | DW_OP_addrx !Word64
- | DW_OP_constx !Word64
- | DW_OP_const_type !Word64 !ByteString
- | DW_OP_fbreg !Int64
- | DW_OP_breg !Int !Int64
- | DW_OP_bregx !Word64 !Int64
- | DW_OP_regval_type !Word64 !Word64
- | DW_OP_dup
- | DW_OP_drop
- | DW_OP_pick !Word8
- | DW_OP_over
- | DW_OP_swap
- | DW_OP_rot
- | DW_OP_deref
- | DW_OP_deref_size !Word8
- | DW_OP_deref_type !Word8 !Word64
- | DW_OP_xderef
- | DW_OP_xderef_size !Word8
- | DW_OP_xderef_type !Word8 !Word64
- | DW_OP_push_object_address
- | DW_OP_form_tls_address
- | DW_OP_call_frame_cfa
- | 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_le
- | DW_OP_ge
- | DW_OP_eq
- | DW_OP_lt
- | DW_OP_gt
- | DW_OP_ne
- | DW_OP_skip !Int16
- | DW_OP_bra !Int16
- | DW_OP_call2 !Word16
- | DW_OP_call4 !Word32
- | DW_OP_call_ref !Word64
- | DW_OP_convert !Word64
- | DW_OP_reinterpret !Word64
- | DW_OP_nop
- | DW_OP_entry_value !ByteString
- | DW_OP_reg !Int
- | DW_OP_regx !Word64
- | DW_OP_implicit_value !ByteString
- | DW_OP_stack_value
- | DW_OP_implicit_pointer !Word64 !Int64
- | DW_OP_piece !Word64
- | DW_OP_bit_piece !Word64 !Word64
- data Range = Range {
- rangeBegin :: !Word64
- rangeEnd :: !Word64
Compile units and declarations
data Endianness Source #
Indicates whether bytes are stored in big or little endian representation.
In a big endian representation, the most significant byte is stored first; In a little endian representation, the most significant byte is stored last.
Constructors
BigEndian | |
LittleEndian |
Instances
Show Endianness Source # | |
Defined in Data.Macaw.Memory Methods showsPrec :: Int -> Endianness -> ShowS # show :: Endianness -> String # showList :: [Endianness] -> ShowS # | |
Eq Endianness Source # | |
Defined in Data.Macaw.Memory | |
Ord Endianness Source # | |
Defined in Data.Macaw.Memory Methods compare :: Endianness -> Endianness -> Ordering # (<) :: Endianness -> Endianness -> Bool # (<=) :: Endianness -> Endianness -> Bool # (>) :: Endianness -> Endianness -> Bool # (>=) :: Endianness -> Endianness -> Bool # max :: Endianness -> Endianness -> Endianness # min :: Endianness -> Endianness -> Endianness # | |
Hashable Endianness Source # | |
Defined in Data.Macaw.Memory | |
Lift Endianness Source # | |
Defined in Data.Macaw.Memory Methods lift :: Quote m => Endianness -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => Endianness -> Code m Endianness # |
mkSections :: Applicative m => (ByteString -> m ByteString) -> m Sections #
firstCUContext :: Endianness -> Sections -> Maybe (Either String CUContext) Source #
getCompileUnit :: CUContext -> (Either String CompileUnit, [String]) Source #
dwarfCompileUnits :: Endianness -> Sections -> ([String], [CompileUnit]) Source #
Deprecated: Use firstCUContext, nextCUContext and getCompileUnit
Return dwarf information out of buffers.
data CompileUnit Source #
The output of one compilation.
Instances
Show CompileUnit Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> CompileUnit -> ShowS # show :: CompileUnit -> String # showList :: [CompileUnit] -> ShowS # | |
Pretty CompileUnit Source # | |
Defined in Data.Macaw.Dwarf |
cuSubprograms :: CompileUnit -> [Subprogram] Source #
lookupSubprogram :: SubprogramRef -> CompileUnit -> Maybe Subprogram Source #
Return subprogram in compile unit
dwarfGlobals :: [CompileUnit] -> [Variable] Source #
This returns all the variables in the given compile units.
Utility function
dwarfInfoFromElf :: forall (v :: Nat). Elf v -> ([String], [CompileUnit]) Source #
Return dwarf information out of an Elf file.
Variables
varOrigin :: Variable -> Maybe VariableRef Source #
A variable reference if this variable comes from an inlined function.
Sub programs
data Subprogram Source #
Constructors
Subprogram | |
Fields
|
Instances
Show Subprogram Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> Subprogram -> ShowS # show :: Subprogram -> String # showList :: [Subprogram] -> ShowS # | |
Pretty Subprogram Source # | |
Defined in Data.Macaw.Dwarf |
data SubprogramDef Source #
Constructors
SubprogramDef | |
Instances
Pretty SubprogramDef Source # | |
Defined in Data.Macaw.Dwarf |
Inlineing
data SubprogramRef Source #
A reference to a subprogram.
Instances
Eq SubprogramRef Source # | |
Defined in Data.Macaw.Dwarf Methods (==) :: SubprogramRef -> SubprogramRef -> Bool # (/=) :: SubprogramRef -> SubprogramRef -> Bool # | |
Ord SubprogramRef Source # | |
Defined in Data.Macaw.Dwarf Methods compare :: SubprogramRef -> SubprogramRef -> Ordering # (<) :: SubprogramRef -> SubprogramRef -> Bool # (<=) :: SubprogramRef -> SubprogramRef -> Bool # (>) :: SubprogramRef -> SubprogramRef -> Bool # (>=) :: SubprogramRef -> SubprogramRef -> Bool # max :: SubprogramRef -> SubprogramRef -> SubprogramRef # min :: SubprogramRef -> SubprogramRef -> SubprogramRef # | |
Pretty SubprogramRef Source # | |
Defined in Data.Macaw.Dwarf |
data VariableRef Source #
A reference to a variable
Instances
Eq VariableRef Source # | |
Defined in Data.Macaw.Dwarf | |
Ord VariableRef Source # | |
Defined in Data.Macaw.Dwarf Methods compare :: VariableRef -> VariableRef -> Ordering # (<) :: VariableRef -> VariableRef -> Bool # (<=) :: VariableRef -> VariableRef -> Bool # (>) :: VariableRef -> VariableRef -> Bool # (>=) :: VariableRef -> VariableRef -> Bool # max :: VariableRef -> VariableRef -> VariableRef # min :: VariableRef -> VariableRef -> VariableRef # | |
Pretty VariableRef Source # | |
Defined in Data.Macaw.Dwarf |
Locations
Provides a way of computing the location of a variable.
Constructors
ComputedLoc !DwarfExpr | |
OffsetLoc !Word64 |
A file and line number for a declaration.
Type information
A reference to a type DIE
typeRefFileOffset :: TypeRef -> Word64 Source #
Return the offset asssociated with the type.
A type form
Constructors
BoolType | A 1-byte boolean value (0 is false, nonzero is true) |
UnsignedIntType !Int | An unsigned integer with the given number of bytes (should be positive) The byte order is platform defined. |
SignedIntType !Int | An signed integer with the given number of bytes (should be positive) The byte order is platform defined. |
FloatType | An IEEE single precision floating point value. |
DoubleType | An IEEE double precision floating point value. |
LongDoubleType | A long double type. |
UnsignedCharType | A 1-byte unsigned character. |
SignedCharType | A 1-byte signed character. |
ArrayType !TypeRef ![Subrange TypeRef] | |
PointerType !(Maybe Word64) !(Maybe TypeRef) |
|
StructType !StructDecl | Denotes a C struct |
UnionType !UnionDecl | Denotes a C union |
EnumType !EnumDecl | |
SubroutinePtrType !SubroutineTypeDecl | |
TypedefType !Typedef | |
TypeQualType !TypeQualAnn | Restrict modifier on type. |
SubroutineTypeF !SubroutineTypeDecl | Subroutine type |
data StructDecl Source #
Constructors
StructDecl | |
Fields
|
Instances
Show StructDecl Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> StructDecl -> ShowS # show :: StructDecl -> String # showList :: [StructDecl] -> ShowS # |
Constructors
UnionDecl | |
Fields
|
Constructors
Member | |
Fields
|
Constructors
EnumDecl | |
Fields
|
data Enumerator Source #
Instances
Show Enumerator Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> Enumerator -> ShowS # show :: Enumerator -> String # showList :: [Enumerator] -> ShowS # |
data SubroutineTypeDecl Source #
Constructors
SubroutineTypeDecl | |
Fields
|
Instances
Show SubroutineTypeDecl Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> SubroutineTypeDecl -> ShowS # show :: SubroutineTypeDecl -> String # showList :: [SubroutineTypeDecl] -> ShowS # |
Constructors
Subrange | |
Fields
|
Constructors
Typedef | |
Fields
|
A qualifier on a type.
Constructors
ConstQual | |
VolatileQual | |
RestrictQual |
data TypeQualAnn Source #
A type qualifier annotation.
Constructors
TypeQualAnn | |
Fields
|
Instances
Show TypeQualAnn Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> TypeQualAnn -> ShowS # show :: TypeQualAnn -> String # showList :: [TypeQualAnn] -> ShowS # |
Name and Description
Constructors
Name | |
Fields |
newtype Description Source #
The value of a DW_AT_description
field.
Note. This is the empty string if th
Constructors
Description | |
Fields |
Instances
Show Description Source # | |
Defined in Data.Macaw.Dwarf Methods showsPrec :: Int -> Description -> ShowS # show :: Description -> String # showList :: [Description] -> ShowS # |
Low-level access
Constructors
DwarfExpr !Reader !ByteString |
Instances
Show DwarfExpr Source # | |
Eq DwarfExpr Source # | |
Ord DwarfExpr Source # | |
Exports of Data.Dwarf
Constructors