GDBEventDispatcher.st
author Jan Vrany <jan.vrany@labware.com>
Sat, 22 May 2021 16:52:20 +0100
changeset 230 ba4b57758e92
parent 228 04ce643219ce
child 235 51f916ee4111
permissions -rw-r--r--
Change `#pushEvent:` to insert event into the current event set ...if any. The reason is that sometimes events are pushed back onto a queue as part of processing command post-execute hook (this is mainly unify internal housekeeping since GDB does not generate various events when state change is caused by an MI command, see [1]). In this case we want these artifical events to be processed within current event set so internal data are in sync when `#send: ... andWait: true` returns. If there's no event set currently being processed, insert event to the end of the queue. [1]: https://sourceware.org/pipermail/gdb/2019-June/047938.html

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

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
"{ Package: 'jv:libgdbs' }"

"{ NameSpace: Smalltalk }"

Object subclass:#GDBEventDispatcher
	instanceVariableNames:'debugger queue lock thread announcer1 announcer2'
	classVariableNames:''
	poolDictionaries:'GDBDebugFlags'
	category:'GDB-Private'
!

!GDBEventDispatcher class methodsFor:'documentation'!

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

This library is free software; you can redistribute it and/or
modify it under the terms of the GNU Lesser General Public
License as published by the Free Software Foundation; either
version 2.1 of the License. 

This library is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Lesser General Public License for more details.

You should have received a copy of the GNU Lesser General Public
License along with this library; if not, write to the Free Software
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
"
! !

!GDBEventDispatcher class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!GDBEventDispatcher methodsFor:'accessing'!

process
    ^ thread

    "Modified: / 26-03-2021 / 13:43:40 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher methodsFor:'adding'!

pushEvent: aGDBEvent
    lock critical:[
        | index |

        Logger 
            log:('event loop: pushing %1 (%2)' bindWith:aGDBEvent class name
                    with:aGDBEvent token)
            severity:#trace
            facility:'GDB'
            originator:self
            attachment:aGDBEvent.

        "/ Sometimes, events are pushed back onto a queue as part of processing
        "/ command post-execute hook (this is mainly unify internal housekeeping
        "/ since GDB does not generate various events when state change is caused by
        "/ an MI command, see [1]).
        "/ 
        "/ In this case we want these artifical events to be processed within current
        "/ event set so internal data are in sync when `#send: ... andWait: true` returns.
        "/ 
        "/ [1]: https://sourceware.org/pipermail/gdb/2019-June/047938.html
        index := queue findFirst:[ :ev | ev isEventSetProcessingFinishedEvent ] ifNone: [queue size + 1].
        queue add: aGDBEvent beforeIndex: index.
    ].
    self start

    "Created: / 02-06-2014 / 22:49:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2018 / 14:30:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 22-05-2021 / 16:49:54 / Jan Vrany <jan.vrany@labware.com>"
!

pushEventSet: aGDBEventSet
    lock critical:[
        queue add: (GDBEventSetProcessingStarted new setEventSet: aGDBEventSet).  
        queue addAll: aGDBEventSet.
        queue add: (GDBEventSetProcessingFinished new setEventSet: aGDBEventSet).
    ].
    self start.

    "Created: / 02-06-2014 / 22:42:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2018 / 14:30:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 17-03-2021 / 12:33:01 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    super initialize.
    queue := OrderedCollection new.
    lock := RecursionLock new.

    "Modified: / 02-10-2018 / 14:13:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-03-2021 / 12:40:41 / Jan Vrany <jan.vrany@labware.com>"
!

setAnnouncer1: anAnnouncer
    announcer1 := anAnnouncer

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

setAnnouncer2: anAnnouncer
    announcer2 := anAnnouncer

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

setDebugger: aGDBDebugger
    debugger := aGDBDebugger

    "Created: / 09-03-2021 / 21:02:59 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher methodsFor:'private'!

dispatchEvent:aGDBEvent
    aGDBEvent debugger: debugger.
    TraceEvents ifTrue:[
        Logger 
            log:('event loop: broadcasting %1 (%2)' bindWith:aGDBEvent class name
                    with:aGDBEvent token)
            severity:#trace
            facility:'GDB'
            originator:self
            attachment:aGDBEvent
    ].
    announcer1 notNil ifTrue:[
        announcer1 announce:aGDBEvent.
    ].
    announcer2 notNil ifTrue:[
        announcer2 announce:aGDBEvent
    ].

    "Created: / 02-06-2014 / 22:58:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 02-10-2018 / 14:36:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-03-2021 / 21:03:21 / Jan Vrany <jan.vrany@labware.com>"
!

dispatchEvents
    "Dispatch all events the queue."

    | event |

    [
        event := nil.
        lock critical:[
            queue notEmpty ifTrue:[event := queue removeFirst]
        ].
        event notNil ifTrue:[
            self dispatchEvent: event
        ].
        event notNil.
    ] whileTrue.

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

!GDBEventDispatcher methodsFor:'queries'!

hasPendingEvents

    "/ Note that there's no obligation for this information to
    "/ be 100% accurate, so no need for symchronization here.
    ^ queue notEmpty. 

    "Created: / 17-03-2021 / 12:36:16 / Jan Vrany <jan.vrany@labware.com>"
!

hasPendingEventsMatching: aBlock

    | anyCommandEventPending |

    "/ Here, synchronization is required since we iterate over
    "/ collection...
    lock critical:[
        anyCommandEventPending := queue anySatisfy: aBlock
    ].
    ^ anyCommandEventPending

    "Created: / 17-03-2021 / 12:37:58 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher methodsFor:'start & stop'!

start
    | t |

    self assert: queue notNil.
    self assert: lock notNil.

     ((t := thread) isNil or:[t isDead]) ifTrue:[
        thread := [
                self dispatchEvents.
                thread := nil.
            ] newProcess.
        thread name:('GDB Event dispatcher').
        "/thread priority:Processor userBackgroundPriority.
        thread addExitAction:[
            thread := nil.
        ].
        thread resume.
    ].

    "Created: / 02-10-2018 / 14:25:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 02-10-2018 / 16:34:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-03-2021 / 21:10:59 / Jan Vrany <jan.vrany@labware.com>"
!

wait
    "Wait until all events are processed"

    | t |

    (t := thread) isNil ifTrue:[^self].
    thread := nil.
    t isDead ifTrue: [ ^ self ].
    t priority:(Processor userSchedulingPriority + 1).

    "Created: / 02-10-2018 / 14:25:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 26-03-2021 / 14:17:11 / Jan Vrany <jan.vrany@labware.com>"
    "Modified (comment): / 26-03-2021 / 21:01:30 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher class methodsFor:'documentation'!

version_HG

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