GDBThread.st
author Jan Vrany <jan.vrany@labware.com>
Fri, 08 Sep 2023 12:40:22 +0100
changeset 317 7f63737e0374
parent 315 91819b724b59
permissions -rw-r--r--
Fix `GDBMIDebugger` after rename of `GDBStXUnixProcess` to `GDBUnixProcess` ...in commit d1422e1ee.

"
jv:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2020-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:#GDBThread
	instanceVariableNames:'id group status info stack'
	classVariableNames:''
	poolDictionaries:''
	category:'GDB'
!

!GDBThread class methodsFor:'documentation'!

copyright
"
jv:libgdbs - GNU Debugger Interface Library
Copyright (C) 2015-now Jan Vrany
Copyright (C) 2020-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.
"
! !

!GDBThread class methodsFor:'instance creation'!

newWithDebugger: debugger id: id group: group
    ^ self new
        setDebugger: debugger;
        setId: id;
        setGroup: group;
        setStatus: GDBThreadStateRunning theOneAndOnlyInstance;
        yourself.

    "Created: / 07-09-2014 / 21:33:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-01-2018 / 22:33:26 / jv"
! !

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

description
    ^ (super description)
        define:#id as:Integer;
        yourself

    "Created: / 06-09-2014 / 02:21:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'accessing'!

group
    ^ group
!

id
    ^ id

    "Created: / 07-09-2014 / 22:41:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

name
    | i |

    i := self info.
    ^ i name ? i targetId.

    "Created: / 10-03-2015 / 00:32:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 22-02-2021 / 13:21:13 / Jan Vrany <jan.vrany@labware.com>"
!

stack
    self ensureIsStopped.
    ^ stack value

    "Created: / 09-09-2014 / 00:02:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-09-2018 / 00:11:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-03-2021 / 14:56:43 / Jan Vrany <jan.vrany@labware.com>"
!

stackButNotStale
    self ensureIsStopped.
    ^ stack valueButNotStale

    "Created: / 10-03-2021 / 15:00:53 / Jan Vrany <jan.vrany@labware.com>"
!

stackPossiblyStale
    self ensureIsStopped.
    ^ stack valuePossiblyStale

    "Created: / 10-03-2021 / 14:55:21 / Jan Vrany <jan.vrany@labware.com>"
!

status
    status isUnknown ifTrue:[ 
        status := self info state
    ].
    ^ status

    "Modified: / 12-07-2017 / 13:36:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

targetId
    ^ self info targetId

    "Created: / 10-03-2015 / 00:32:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'accessing-private'!

info
    info isNil ifTrue:[
        info := GDBTransientDataHolder debugger: debugger factory:[ 
            | result infos |

            result := debugger send: (GDBMI_thread_info new arguments: (Array with: id)).
            infos := result propertyAt: #threads.
            self assert: (infos isEmptyOrNil or:[ infos size == 1 and:[ infos first id = id ] ]).
            infos isEmptyOrNil 
                ifTrue:[ GDBThreadInfo new setId: id state: GDBThreadStateTerminated theOneAndOnlyInstance ] 
                ifFalse:[ infos first ]
        ].
    ].
    ^ info value

    "Created: / 08-03-2015 / 09:07:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-11-2017 / 20:21:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'displaying'!

displayOn: aStream
    aStream nextPutAll: 'Thread '.
    id printOn: aStream base: 10 size: 2 fill: $0.
    aStream nextPutAll: ' ['.
    self status printOn: aStream.
    aStream nextPutAll: ']'.   
    self isRunning ifTrue: [ 
        aStream nextPutAll: ' "'; nextPutAll: self name; nextPut: $"
    ].

    "Created: / 29-08-2023 / 11:43:02 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 29-08-2023 / 13:45:23 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBThread methodsFor:'event handling'!

onRunningEvent: aGDBRunningEvent
    self assert: (aGDBRunningEvent threads includes: self).
    status := GDBThreadStateRunning theOneAndOnlyInstance.

    "Created: / 12-07-2017 / 13:50:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-07-2023 / 17:18:19 / Jan Vrany <jan.vrany@labware.com>"
!

onStoppedEvent: aGDBStoppedEvent
    self assert: (aGDBStoppedEvent threads includes: self).
    status := GDBThreadStateStopped theOneAndOnlyInstance.
    aGDBStoppedEvent stoppedThread == self ifTrue: [
        "/ Carefull - not all stop events have frame, for example
        "/ solib-events have not!!
        aGDBStoppedEvent frame notNil ifTrue:[
            aGDBStoppedEvent frame   
                setDebugger: debugger;
                setThread: self;
                setLevel: 0.
        ].
    ].

    "Created: / 12-07-2017 / 13:50:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-07-2023 / 17:18:15 / Jan Vrany <jan.vrany@labware.com>"
!

onThreadSelectedEvent: aGDBThreadSelectedEvent
    |  frame |

    frame := aGDBThreadSelectedEvent frame.

    aGDBThreadSelectedEvent setThread: self.
    "/ Be carefull, thread may be running!!
    (self isStopped and:[frame notNil]) ifTrue:[ 
        "/ Beware, `self stack` may execute another command
        "/ and this is called from within event dispatch loop.
        "/ 
        "/ This was not possible before, but now it should
        "/ (see commit bf5cfa214dd4)
        aGDBThreadSelectedEvent setFrame: (self stack at: (frame level + 1))
    ] ifFalse:[ 
        "/ If it is running, at least fixup event's frame, if there's any (it may not
        "/ if the thread is running at the time of =thread-select event.
        "/ Uff, so many cases...
        frame notNil ifTrue:[
            frame 
                setDebugger: debugger;
                setThread: self.
        ].
    ].

    "Created: / 29-07-2018 / 22:21:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-11-2019 / 22:09:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-01-2022 / 15:23:24 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBThread methodsFor:'initialization'!

setDebugger: aGDBDebugger
    debugger := aGDBDebugger.
    stack := GDBTransientDataHolder debugger: debugger factory:[ :old | 
        [
            | result depth new oldFrameIndex oldFrame newFrameIndex newFrame |

            result := debugger send: (GDBMI_stack_info_depth new arguments: (Array with: '--thread' with: id with: 100)).
            depth := result propertyAt: #depth.
            result := debugger send: (GDBMI_stack_list_frames new arguments: (Array with:  '--thread' with: id with: 0 with: depth - 1 )).
            new := result propertyAt: #stack.

            "/ Now, walk from the bottom of the stack (the least recent frame) and
            "/ ipdate `new` array with frames from `old` array to preserve the
            "/ identity.
            newFrameIndex := new size.
            oldFrameIndex := old size.
            [ newFrameIndex > 0 and:[ oldFrameIndex > 0 ] ] whileTrue:[ 
                newFrame := new at: newFrameIndex.
                oldFrame := old at: oldFrameIndex.
                "/ If frame addrs matches, both frames really represent the same thing so
                "/ just replace the 'new' frame with the 'old'.
                newFrame addr = oldFrame addr ifTrue:[ 
                    "/ OK, the two frames are really the same thing
                    oldFrame setLevel: newFrame level. "/ Update level
                    new at: newFrameIndex put: (old at: oldFrameIndex).
                    newFrameIndex := newFrameIndex - 1.
                    oldFrameIndex := oldFrameIndex - 1.
                ] ifFalse:[ 
                    "/ No, frame pc differs. This is the first time they differ so
                    "/ it could be the same frame just on different PC (since PC of
                    "/ caller did not change). Subsequent frames could also be "same"
                    "/ if they're inlined into caller - in this case, the PC (#addr) of
                    "/ the caller frame and inlined callee are the same.
                    "/ 
                    "/ So, we update subsequent frames as long as 
                    "/  a) function names are the same AND
                    "/  b) PC is the same as PC of its caller
                    "/
                    "/ Complicated, isn't it?
                    | oldAddr newAddr |
                    oldAddr := oldFrame addr.
                    newAddr := newFrame addr.
                    [ newFrameIndex > 0 and:[ oldFrameIndex > 0 ] ] whileTrue:[
                        newFrame := new at: newFrameIndex.
                        oldFrame := old at: oldFrameIndex.    
                        ("a)"oldFrame func = newFrame func and: ["b)"oldFrame addr = oldAddr and:[newFrame addr = newAddr]]) ifTrue:[ 
                            "/ Update the frame...
                            oldFrame setAddr: newFrame addr.
                            oldFrame setLine: newFrame line.
                            oldFrame setLevel: newFrame level.
                            new at: newFrameIndex put: (old at: oldFrameIndex).
                            newFrameIndex := newFrameIndex - 1.
                            oldFrameIndex := oldFrameIndex - 1.    
                        ] ifFalse:[
                            "/ Terminate the loop, see the condition above.
                            oldFrameIndex := 0. 
                        ].
                    ]
                ].
            ].
            "/ For the remaining really new frames, set the debugger
            "/ and the thread.
            [ newFrameIndex > 0 ] whileTrue:[ 
                newFrame := new at: newFrameIndex.
                newFrame setDebugger: debugger.
                newFrame setThread: self.
                newFrameIndex := newFrameIndex - 1.
            ].
            new
        ] on: GDBError do:[ :ex |
            self isRunning ifFalse:[
                ex pass.
            ].
            old.
        ].
    ].

    "Created: / 10-03-2021 / 15:02:28 / Jan Vrany <jan.vrany@labware.com>"
!

setGroup: aGDBThreadGroup
    self assert: group isNil.
    group := aGDBThreadGroup.

    "Created: / 07-09-2014 / 21:32:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setId: tid
    self assert: id isNil.
    id := tid.

    "Created: / 07-09-2014 / 21:31:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 09:08:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setStatus: aGDBThreadState
    status := aGDBThreadState

    "Created: / 12-07-2017 / 13:43:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setTerminated

    "Created: / 07-09-2014 / 21:37:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 09:08:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'inspecting'!

inspector2TabBacktrace
    <inspector2Tab>
    ^ (self newInspector2Tab)
        label:'Backtrace';
        priority:60;
        list:[ self stack ];
        font: CodeView defaultFont;
        yourself

    "Created: / 01-09-2023 / 22:29:26 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 02-09-2023 / 15:34:54 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBThread methodsFor:'printing & storing'!

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

    aStream nextPutAll:'thread  '.
    id printOn:aStream.
"/    aStream nextPutAll:'in group '.
"/    group id printOn:aStream.
    aStream nextPutAll:' ['.
    self status printOn:aStream.
    aStream nextPutAll:']'.

    "Modified: / 08-03-2015 / 09:07:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'private'!

ensureIsStopped
    self isStopped ifFalse:[
        (GDBInvalidObjectError newException)
            parameter:self;
            messageText:'Invalid state (thread is running or already dead)';
            raise.
    ].

    "Created: / 09-09-2014 / 00:04:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-09-2014 / 23:51:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread methodsFor:'testing'!

isDead
    ^ self isTerminated

    "Created: / 22-09-2014 / 00:54:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 12:35:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 14-01-2018 / 22:34:04 / jv"
!

isRunning
    ^ self status isRunning

    "Created: / 07-09-2014 / 23:23:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 09:08:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isStopped
    ^ self status isStopped

    "Created: / 07-09-2014 / 23:23:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 09:08:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isTerminated
    ^ self status isTerminated

    "Created: / 07-09-2014 / 23:23:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-03-2015 / 09:08:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isValid
    ^ group isValid and:[ self isDead not ]

    "Created: / 04-02-2018 / 21:31:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBThread class methodsFor:'documentation'!

version_HG

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