GDBEventDispatcher.st
author Jan Vrany <jan.vrany@labware.com>
Mon, 04 Sep 2023 14:00:57 +0100
changeset 314 4a2ef5a087f0
parent 309 f2481d09d58e
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 }"

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

!GDBEventDispatcher 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.
"
! !

!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 |

        TraceEvents ifTrue: [
            Logger trace:'event loop: pushing %1' with: 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 := 1.
        [ index <= queue size and:[(queue at: index) isEventSetProcessingFinishedEvent not] ] whileTrue: [ 
            index := index + 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: / 14-07-2023 / 14:29:22 / Jan Vrany <jan.vrany@labware.com>"
!

pushEventSet: aGDBEventSet
    lock critical:[
        queue add: (GDBEventSequenceProcessingStarted new setEventSet: aGDBEventSet).  
        queue addAll: aGDBEventSet.
        queue add: (GDBEventSequenceProcessingFinished 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: / 06-09-2021 / 15:01:58 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBEventDispatcher methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

    super initialize.
    queue := OrderedCollection new.
    lock := GDBPortlib current newMutex.

    "Modified: / 02-10-2018 / 14:13:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 25-08-2023 / 15:51:36 / 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
    | deliveries |

    aGDBEvent debugger: debugger.
    TraceEvents ifTrue:[
        Logger 
            log:('event loop: broadcasting %1' bindWith:aGDBEvent)
            severity:#trace
            facility:'GDB'
            originator:self
            attachment:aGDBEvent
    ].
    announcer1 notNil ifTrue:[
        deliveries isNil ifTrue: [ deliveries := OrderedCollection new ].
        announcer1 subscriptionsFor: aGDBEvent do: [ :subscription|
            deliveries add: (GDBEventDelivery new subscription: subscription event: aGDBEvent)
        ].
        "/ announcer1 announce:aGDBEvent.
    ].
    announcer2 notNil ifTrue:[
        deliveries isNil ifTrue: [ deliveries := OrderedCollection new ].
        announcer2 subscriptionsFor: aGDBEvent do: [ :subscription|
            deliveries add: (GDBEventDelivery new subscription: subscription event: aGDBEvent)
        ].
        "/ announcer2 announce:aGDBEvent
    ].
    deliveries notEmptyOrNil ifTrue: [ 
        lock critical:[
            deliveries reverseDo: [:delivery | queue addFirst: delivery ]
        ]
    ].

    "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: / 22-02-2022 / 11:57:30 / Jan Vrany <jan.vrany@labware.com>"
!

dispatchEvents
    "Dispatch all events the queue."

    | currentQueue currentEvent |

    currentQueue := queue.
    [
        currentEvent := nil.
        lock critical:[
            currentQueue notEmpty ifTrue:[currentEvent := currentQueue removeFirst]
        ].
        currentEvent notNil ifTrue:[
            currentEvent dispatchUsing: self
        ].
        currentEvent notNil.
    ] whileTrue.

    "Created: / 26-03-2021 / 21:10:49 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 29-03-2021 / 12:18:13 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 28-06-2021 / 12:07:26 / 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'!

restart
    "'Restarts' the event dispatch loop if it is running, forcing
     remaining events (if any) to be processes in a new thread.

     This is done by moving all events from current queue object
     into a new one and then swapping then. This works, because
     #dispatchEvents do not read queue instvar directly."

    lock critical: [ 
        | new |

        new := queue copy.
        queue removeAll.
        queue := new.
    ].
    thread := nil.
    self start.

    "Created: / 27-03-2021 / 08:26:50 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 28-03-2021 / 22:10:29 / Jan Vrany <jan.vrany@labware.com>"
!

start
    | t |

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

     ((t := thread) isNil or:[t isDead]) ifTrue:[
        thread := [
                [
                    self dispatchEvents.
                ] ensure: [ 
                    Processor activeProcess == thread ifTrue: [ 
                        thread := nil.
                    ].
                ].
            ] newProcess.
        thread name:('GDB Event dispatcher').
        "/thread priority:Processor userBackgroundPriority.
        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: / 28-03-2021 / 22:05:46 / 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> $'
! !