GDBFrame.st
author Jan Vrany <jan.vrany@labware.com>
Mon, 04 Sep 2023 14:00:57 +0100
changeset 314 4a2ef5a087f0
parent 311 aaa582ae8897
child 315 91819b724b59
permissions -rw-r--r--
Add MI parser test This commit add test to parse real-world frament which failed to Pharo properly at some point. It is encoded here as bytearray to make sure all the characters are preserved exactly as they were.

"
jv:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2021-2023 LabWare

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
"
"{ Package: 'jv:libgdbs' }"

"{ NameSpace: Smalltalk }"

GDBDebuggerObject subclass:#GDBFrame
	instanceVariableNames:'thread level addr func file fullname line arch from variables
		registers registersChanges'
	classVariableNames:''
	poolDictionaries:''
	category:'GDB'
!

!GDBFrame class methodsFor:'documentation'!

copyright
"
jv:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2021-2023 LabWare

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.
"
! !

!GDBFrame class methodsFor:'accessing - GDB value descriptors'!

description
    ^ (super description)
        define:#level as:Integer;
        define:#func as:String;
        define:#file as:String;
        define:#fullname as:String;
        define:#line as:Integer;
        define:#from as:String;
        define:#addr as:Integer;
        yourself

    "Created: / 16-09-2014 / 23:59:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-02-2018 / 08:27:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBFrame methodsFor:'accessing'!

addr
    addr isNil ifTrue: [ 
        | result updated |

        result := debugger send: (GDBMI_stack_list_frames new arguments: (Array with:  '--thread' with: thread id with: level with: level )).
        updated := (result propertyAt: #stack) first.
        addr := updated addr.
    ].
    ^ addr

    "Modified: / 14-10-2021 / 14:16:10 / Jan Vrany <jan.vrany@labware.com>"
!

address
    ^ self addr

    "Created: / 03-07-2018 / 15:10:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

arch
    arch isNil ifTrue:[
        arch := GDBArchitecture named: 'unknown'.
    ].
    arch isString ifTrue:[ 
        arch := GDBArchitecture named: arch
    ].
    ^ arch

    "Created: / 16-08-2018 / 06:59:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-08-2018 / 09:04:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

disassemble
    "Return instructions for a function of this frame"

    | disassembly |

    (debugger hasFeature:'data-disassemble-a-option') ifTrue:[
        disassembly := debugger disassembleFunction: '0x', addr hexPrintString.  
    ] ifFalse:[ 
        disassembly := debugger disassembleFile: file  line: line count: nil.
    ].
    disassembly do:[ :each | each setArchitecture: self arch ].  
    ^ disassembly

    "Created: / 22-06-2018 / 12:47:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-08-2018 / 09:40:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

file
    "Return filename (path) containing frame's function source."

    | f |

    "/ GDB/MI provides two paths, `file` and `fullname`. 
    "/ 
    "/ However, sometimes GDB gets confused and does not return
    "/ anything directly useful, especially when debug info contains
    "/ relative paths with multiple segments. 
    "/ 
    "/ As a courtesy to the user, in that case try to resolve full
    "/ path here too. Hence the code below.
    "/
    "/ To avoid re-resolving of file each time this method is called,
    "/ cache resolved Filename in `fullname` instvar. 

    fullname isFilename ifTrue:[ 
        "/ Already resolved by the code below
        ^ fullname pathName
    ].

    f := fullname ? file.
    f isNil ifTrue:[ ^ nil ].
    f := (String withAll: f) replaceAll: $/ with: Filename separator.
    f := f asFilename.

    "/ check, if GDB returned correctly resolved filename...
    f exists ifTrue:[
        fullname := f.
        ^ fullname pathName
    ].

    "/ ...if not, try to look it up in source directories...
    self debugger directories do:[:d |
        fullname notNil ifTrue:[
            f := d asFilename / fullname.
            f exists ifTrue:[ 
                fullname := f.
                ^ fullname pathName.
            ].
        ].
        file notNil ifTrue:[
            f := d asFilename / file.
            f exists ifTrue:[ 
                fullname := f.
                ^ fullname pathName.
            ]. 
        ].
    ].

    "/ ...if not found there...
    ^ nil

    "Modified: / 22-03-2018 / 16:52:52 / jv"
    "Modified: / 26-03-2019 / 10:30:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

from
    ^ from
!

func
    ^ func
!

level
    ^ level
!

line
    ^ line
!

registers
    "Return a list of machine registers and their corresponding
     values in this frame (as list of GDBRegisterWithValue)"

    registers isNil ifTrue:[
        | registersFile result |

        registersFile := self registersFile.

        "/ Second, fetch values and populate a collection of registers (as `GDBRegisterWithValue`). This is done
        "/ onlt once, later on, the value of registers is updated automagically (see `GDBRegisterWithValue >> value`).
        result := debugger send: (GDBMI_data_list_register_values new arguments: (Array with: '--thread' with: thread id with: '--frame' with: level with: 'r') , (self arch registerNumbersToDisplayUsing: registersFile)).
        registers := result propertyAt: #'register-values'.
        registers do:[:value | value setFrame: self; setRegisterFrom: registersFile ].
    ].
    ^ registers value

    "Created: / 26-09-2018 / 09:51:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-05-2020 / 13:59:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 21-11-2022 / 16:24:40 / Jan Vrany <jan.vrany@labware.com>"
!

thread
    ^ thread
!

variables
    self ensureIsValid.
    variables isNil ifTrue:[
        variables := GDBTransientDataHolder debugger: debugger factory:[ :old |
            | result new |

            result := debugger send: (GDBMI_stack_list_variables new arguments: (Array with: '--thread' with: thread id with: '--frame' with: level with: '--simple-values')).
            new := (result propertyAt: #variables) ? #().
            old notNil ifTrue:[ 
                old size == new size ifTrue:[
                    1 to: new size do:[:i | 
                        | oldVar newVar |

                        oldVar := old at: i.
                        newVar := new at: i.
                        newVar name = oldVar name ifTrue:[  
                            oldVar updateFrom: newVar.
                            new at: i put: oldVar.
                        ].
                    ].
                ] ifFalse:[ 
                    "/ This happens when execution enter a new scope on language level.
                    "/ For example:
                    "/ 
                    "/  1   int i;
                    "/  2   {
                    "/  3       int j;
                    "/  4       ...
                    "/  5   }
                    "/ 
                    "/ When execution steps from line 1 to line 3, a new variable `j`
                    "/ appear so we end up here.
                    new do:[:newVar | newVar setFrame: self ]
                ].
            ] ifFalse:[ 
                new do:[:newVar | newVar setFrame: self ]
            ].
            new
        ].
    ].
    ^ variables value

    "Created: / 27-02-2015 / 14:56:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-03-2019 / 10:38:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBFrame methodsFor:'accessing - registers'!

getRegister: name
    | registerAndValue |

    registerAndValue := self registers detect: [ :each | each name = name asString ]
                                       ifNone: [ Object keyNotFoundError: 'No such register: ', name asString ].
    ^ registerAndValue value.

    "Created: / 10-09-2021 / 14:09:59 / Jan Vrany <jan.vrany@labware.com>"
!

setRegister: name to: value
    | registerAndValue |

    registerAndValue := self registers detect: [ :each | each name = name asString ] ifNone: [ nil ].

    (registerAndValue isNil and:[ name = 'pc' ]) ifTrue: [ 
        "Treat 'pc' as program counter register, even though it may be named
         differently on different architectures"
         registerAndValue := self registers detect: [ :each | each name = arch registerNameOfProgramCounter ] ifNone: [ nil ].
    ].

    registerAndValue isNil ifTrue:[
        Object keyNotFoundError: 'No such register: ', name.
    ].
    registerAndValue value: value

    "Created: / 10-09-2021 / 15:14:56 / Jan Vrany <jan.vrany@labware.com>"
    "Modified (format): / 09-12-2022 / 12:51:46 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame methodsFor:'displaying'!

displayOn: aStream
    level printOn:aStream base: 10 size: 2 fill: Character space.
    aStream nextPutAll:' 0x'.
    self addr printOn:aStream base: 16 size: (self arch sizeofPointer * 2) fill: $0.
    aStream nextPutAll:' '.
    func notNil ifTrue:[
        aStream nextPutAll: func.
    ] ifFalse:[ 
        aStream nextPutAll: '?'
    ].
    file notNil ifTrue:[
        aStream nextPutAll:' ('.
        aStream nextPutAll: (file copyFrom: (file lastIndexOf: Filename separator) + 1 to: file size).
        line notNil ifTrue:[
            aStream nextPutAll:':'.
            line printOn:aStream.
        ].
        aStream nextPutAll:')'.
    ].

    "Created: / 29-08-2023 / 11:48:00 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 30-08-2023 / 11:53:40 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame methodsFor:'initialization'!

setAddr: aString
    addr := aString

    "Created: / 31-01-2018 / 09:50:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setLevel: anInteger
    level := anInteger

    "Created: / 15-02-2018 / 08:34:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Created: / 02-02-2018 / 12:16:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setLine: anInteger
    line := anInteger

    "Created: / 01-02-2018 / 10:09:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setThread: aGDBThread
    self assert: (thread isNil or:[ thread == aGDBThread ]).
    thread := aGDBThread

    "Created: / 30-01-2018 / 15:56:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-05-2021 / 15:45:08 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation if the receiver to the argument, aStream"

    super printOn: aStream.
    aStream nextPutAll:'('.
    "/ In rare occations, level may be nil, for example if frame object 
    "/ comes from stopped event. sigh...
    level isNil ifTrue: [
        aStream nextPutAll: ' ?'
    ] ifFalse: [  
        level printOn:aStream base: 10 size: 2 fill: Character space.
    ].
    aStream nextPutAll:' '.
    addr printOn:aStream.
    aStream nextPutAll:' '.
    func printOn:aStream.
    aStream nextPutAll:' - '.
    file printOn:aStream.
    aStream nextPutAll:':'.
    line printOn:aStream.
    aStream nextPutAll:')'.

    "Modified: / 27-02-2015 / 15:21:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-02-2022 / 11:24:30 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame methodsFor:'private'!

invalidate
    self invalidate: nil

    "Created: / 10-09-2021 / 15:37:31 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 18-11-2021 / 12:01:12 / Jan Vrany <jan.vrany@labware.com>"
!

invalidate: registerOrNil
    variables notNil ifTrue: [ variables invalidate ].
    registerOrNil isNil ifTrue: [
        "/ registers notNil ifTrue: [ registers do:[:each | each invalidate ] ]
        "/ registersChanges notNil ifTrue: [ registersChanges invalidate ].
    ] ifFalse: [
        self assert: registers notNil.
        self assert:(registers includes: registerOrNil).
        registerOrNil invalidate.
    ].
    "/ We also have to invalidate the frame PC because it may have changed
    "/ (for example, someone set the PC register to an arbitrary value).
    "/ 
    "/ New PC is lazily refetched in #addr.
    addr := nil

    "Created: / 18-11-2021 / 12:01:17 / Jan Vrany <jan.vrany@labware.com>"
    "Modified (format): / 21-11-2022 / 17:07:37 / Jan Vrany <jan.vrany@labware.com>"
!

registersChanges
    registersChanges isNil ifTrue:[ 
        self isValid ifTrue:[
            registersChanges := GDBTransientDataHolder debugger: debugger factory: [ :old |
                old isNil ifTrue:[ 
                    #()
                ] ifFalse:[
                    | result displayed changed |

                    "/ Sigh, on some buggy architectures and/or simulators (e.g., RISC-V on QEMU as of 2020-05-21)
                    "/ GDB fails to fetch some registers when issuing -data-list-changed-registers or later 
                    "/ when issuing -data-list-register-values.
                    "/ 
                    "/ To workaround that, handle such an error and then conservatively refetch all 
                    "/ (displayed) registers.
                    "/ 
                    "/ Essentially a hack for RISC-V and QEMU (perhaps needed for others, too)
                    displayed := self arch registerNumbersToDisplayUsing: self registersFile.
                    [
                        result := debugger send: (GDBMI_data_list_changed_registers new arguments: (Array with: '--thread' with: thread id with: '--frame' with: level)).
                        changed := (result propertyAt: #'changed-registers') ? #().
                        displayed notEmpty ifTrue: [ 
                            changed := changed intersect: displayed.
                        ].
                    ] on: GDBCommandFailedError do:[
                        changed := displayed.
                    ].

                    changed notEmptyOrNil ifTrue:[
                        [
                            result := debugger send: (GDBMI_data_list_register_values new arguments: (Array with: '--thread' with: thread id with: '--frame' with: level with: 'r') , changed).
                            (result propertyAt: #'register-values') asSet.
                        ] on: GDBCommandFailedError do: [:ex | 
                            "/ Oops, some error. Thread / frame died meanwhile?
                            #()
                        ].
                    ] ifFalse:[ 
                        #()
                    ].
                ].
            ].
        ] ifFalse:[ 
            registersChanges := #().
        ].
    ].
    ^ registersChanges value

    "Created: / 26-09-2018 / 22:35:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 22-05-2020 / 14:49:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2021 / 13:02:09 / Jan Vrany <jan.vrany@labware.com>"
!

registersFile
    "Return a file of registers available for this frame, as a Dictionary 
     mapping GDB internal register number to instance of GDBRegister."

    "/ To reduce MI communication overhead, registers are cached
    "/ in shared cache kept in process group (inferior). Caching is 
    "/ based on an assumption that while each frame may have different 
    "/ architecture, it is unlikely that  different frames with same 
    "/ architecture would have different set of registers.
    ^ self thread group registersMap at: self arch ifAbsentPut:[ 
        | result registersSet |
        result := debugger send: (GDBMI_data_list_register_names arguments: (Array with: '--thread' with: self thread id with: '--frame' with: self level)).
        registersSet := Dictionary new.
        (result propertyAt: 'register-names') withIndexDo:[ :name :number | 
            name notEmpty ifTrue:[
                "/ Note, that GDB register indices starts with 0 (zero) like in C!!
                registersSet at: number - 1 put: (GDBRegister new setNumber: number - 1; setName: name)
            ].
        ].
        registersSet
    ].

    "Created: / 22-05-2020 / 13:56:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBFrame methodsFor:'queries'!

hasSource
    "Return `true` if a source file can is available,
     `false` otherwise."

    ^ self file notNil

    "Created: / 02-10-2018 / 10:28:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hasSymbol
    "Return `true` if GDB find a symbol (function name) 
     for this frame's code, `false` otherwise."

    "/ Following test is rally, really stupid, but at
    "/ the moment there's no better way. We'd need to fix GDB/MI
    "/ to report frame type too. Sigh.
    ^ func notNil 
        and:[ func ~= '??' 
        and: [(func includesString: 'signal handler called') not]]

    "Created: / 02-10-2018 / 09:47:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 07-10-2018 / 08:22:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isSameAs: anotherFrame
    ^ thread == anotherFrame thread
        and: [ level == anotherFrame level
        and: [ func = anotherFrame func 
        and: [ self arch == anotherFrame arch ] ] ]

    "Created: / 18-11-2021 / 17:39:43 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame methodsFor:'testing'!

isValid
    ^ thread isValid and:[self addr notNil]

    "Modified: / 04-02-2018 / 21:30:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-11-2021 / 12:07:51 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBFrame class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !