GDBDriver.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 09 Jun 2014 10:28:46 +0100
changeset 10 f04a22c9b16c
parent 9 5cc8797f6523
child 11 474fbb650afe
permissions -rw-r--r--
Use special PTY for inferior input/output... ...so gdb control streams are not interleaved with inferior's input/output.

"{ Package: 'jv:libgdbs' }"

Object subclass:#GDBDriver
	instanceVariableNames:'pid debuggerInput debuggerOutput inferiorInput inferiorOutput
		eventAnnouncer eventQueue eventQueueLock eventQueueNotifier
		eventDispatchProcess eventPumpProcess'
	classVariableNames:''
	poolDictionaries:'GDBDebugFlags'
	category:'GDB-Private'
!


!GDBDriver class methodsFor:'instance creation'!

debuggerPid:pidArg debuggerInput:inputArg debuggerOutput:outputArg inferiorInput:inferiorInputArg inferiorOutput:inferiorOutputArg 
    ^ self new 
        initializeWithDebuggerPid:pidArg
        debuggerInput:inputArg
        debuggerOutput:outputArg
        inferiorInput:inferiorInputArg
        inferiorOutput:inferiorOutputArg

    "Created: / 26-05-2014 / 13:35:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-06-2014 / 09:20:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver methodsFor:'accessing'!

eventAnnouncer
    ^ eventAnnouncer
!

inferiorInput
    ^ inferiorInput
!

inferiorOutput
    ^ inferiorOutput
! !

!GDBDriver methodsFor:'event dispatching'!

eventDispatchLoop
    "raise an error: this method should be implemented (TODO)"

    [  
        | eventQueueEmpty |

        eventQueueEmpty := false.
        [ eventQueueEmpty ] whileFalse:[
            | event |

            event := nil.
            eventQueueLock critical:[ 
                eventQueueEmpty := eventQueue isEmpty.
                eventQueueEmpty ifFalse:[ 
                    event := eventQueue removeFirst.
                ]
            ].
            eventQueueEmpty ifFalse:[
                [
                    self eventDispatchSingle: event.
                ] on: Error do:[:ex | 
                    "/ Pass
                ].
            ].
        ].
        pid isNil ifTrue:[ ^ self ]. "/ gdb process terninated
        eventQueueNotifier wait.
    ] loop.

    "Created: / 02-06-2014 / 22:51:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 04-06-2014 / 09:16:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eventDispatchSingle: aGDBEvent
    TraceEvents ifTrue:[ 
        Logger log: ('event loop: broadcasting %1 (%2)' bindWith: aGDBEvent class name with: aGDBEvent token) severity: #trace facility: 'GDB'
    ].
    eventAnnouncer announce: aGDBEvent

    "Created: / 02-06-2014 / 22:58:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-06-2014 / 09:21:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eventDispatchStart
    eventDispatchProcess isNil ifTrue:[
        eventDispatchProcess := [
                TraceEvents ifTrue:[
                    Logger log: 'event loop: starting' severity: #trace facility: 'GDB'
                ].
                self eventDispatchLoop.
            ] newProcess.
        eventDispatchProcess name:('GDB Event dispatcher (%1)' bindWith:pid).
        eventDispatchProcess priority:Processor userBackgroundPriority.
        eventDispatchProcess addExitAction:[ 
            eventDispatchProcess := nil. 
            TraceEvents ifTrue:[
                Logger log: 'event loop: terminated' severity: #trace facility: 'GDB'
            ].
        ].
        eventDispatchProcess resume.
    ].

    "Created: / 02-06-2014 / 22:51:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-06-2014 / 09:27:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eventDispatchStop
    | t |

    t := eventDispatchProcess.
    (t notNil and:[ t isDead not]) ifTrue:[ 
        eventDispatchProcess := nil.
        t terminate.
         "/ raise its prio to make it terminate quickly
        t priority:(Processor userSchedulingPriority + 1)                       
    ].

    "Created: / 02-06-2014 / 22:52:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver methodsFor:'event handling'!

onCommand: aGDBCommandEvent
    | command |

    command := aGDBCommandEvent command.
    command token notNil ifTrue:[ 
        debuggerInput nextPutAll: command token printString.
    ].
    debuggerInput nextPutLine: command asString.

    "Created: / 02-06-2014 / 23:38:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver methodsFor:'event pump'!

eventPumpLoop
    | parser |

    parser := GDBParser on: debuggerOutput.
    [ debuggerOutput atEnd ] whileFalse:[ 
        | eventset |

        [
            [ 
                eventset := parser parseOutput.
            ] on: StreamNotOpenError do:[
                ^ self.
            ].
            self pushEventSet: eventset.
        ] on: AbortOperationRequest do:[
            | terminator i c |

            terminator := '(gdb)'.
            i := 1.
            debuggerOutput notNil ifTrue:[
                [ debuggerOutput atEnd not and: [i <= terminator size ] ] whileTrue:[ 
                    c := debuggerOutput next.
                    c == (terminator at: i) ifTrue:[ 
                        i := i + 1.
                    ] ifFalse:[ 
                        i := 1.
                    ].
                ].
                debuggerOutput next. "/ read nl.
            ] ifFalse:[ 
                ^ self.
            ].
        ]
    ]

    "Created: / 02-06-2014 / 22:38:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-06-2014 / 00:54:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eventPumpStart
    eventPumpProcess isNil ifTrue:[
        eventPumpProcess := [
                TraceEvents ifTrue:[
                    Logger log: 'event pump: starting' severity: #trace facility: 'GDB'
                ].
                self eventPumpLoop
            ] newProcess.
        eventPumpProcess name:('GDB Event pump (%1)' bindWith:pid).
        eventPumpProcess priority:Processor userBackgroundPriority.
        eventPumpProcess addExitAction:[ 
            TraceEvents ifTrue:[
                Logger log: 'event pump: terminated' severity: #trace facility: 'GDB'
            ].
            eventPumpProcess := nil. 
        ].
        eventPumpProcess resume.
    ].

    "Created: / 02-06-2014 / 22:38:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-06-2014 / 09:27:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

eventPumpStop
    | t |

    t := eventPumpProcess.
    (t notNil and:[ t isDead not]) ifTrue:[ 
        eventPumpProcess := nil.
        t terminate.
         "/ raise its prio to make it terminate quickly
        t priority:(Processor userSchedulingPriority + 1)                       
    ].

    "Created: / 02-06-2014 / 22:40:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver methodsFor:'events'!

pushEvent: aGDBEvent
    eventQueueLock critical:[
        eventQueue add: aGDBEvent.
        eventQueueNotifier signalForAll.
    ].

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

pushEventSet: aGDBEventSet
    eventQueueLock critical:[
        eventQueue addAll: aGDBEventSet.
        eventQueueNotifier signalForAll.
    ].

    "Created: / 02-06-2014 / 22:42:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver methodsFor:'initialize & release'!

initializeWithDebuggerPid:pidArg debuggerInput:inputArg debuggerOutput:outputArg inferiorInput:inferiorInputArg inferiorOutput:inferiorOutputArg 
    pid := pidArg.
    debuggerInput := inputArg.
    debuggerOutput := outputArg.
    inferiorInput := inferiorInputArg.
    inferiorOutput := inferiorOutputArg.
    eventQueue := OrderedCollection new.
    eventQueueLock := RecursionLock new.
    eventQueueNotifier := Semaphore new.
    eventAnnouncer := Announcer new.
    eventAnnouncer 
        when:GDBCommandEvent
        send:#onCommand:
        to:self.

    "Created: / 26-05-2014 / 13:35:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-06-2014 / 09:14:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

release
    pid notNil ifTrue:[
        OperatingSystem sendSignal:(OperatingSystem sigKILL) to:pid.       
    ]

    "Created: / 26-05-2014 / 21:30:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 03-06-2014 / 00:55:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

released: status
    TraceProcesses ifTrue:[ 
        Logger log: ('gdb process: terminated with status %1' bindWith: status code)  severity: #trace facility: 'GDB'.
    ].
    TraceProcesses ifTrue:[ 
        Logger log: ('gdb process: waiting for event pump to finish' bindWith: status code)  severity: #trace facility: 'GDB'.
    ].
    [ eventPumpProcess notNil ] whileTrue:[ 
        Delay waitForMilliseconds: 200.  
    ].
    TraceProcesses ifTrue:[ 
        Logger log: ('gdb process: event pump finished' bindWith: status code)  severity: #trace facility: 'GDB'.
    ].
    pid := nil.       
    eventQueueNotifier signalForAll.           
    debuggerInput notNil ifTrue:[ 
        debuggerInput close.
        debuggerInput := nil.
    ].
    debuggerOutput notNil ifTrue:[ 
        debuggerOutput close.
        debuggerOutput := nil.
    ].

    "Created: / 26-05-2014 / 21:31:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-06-2014 / 09:20:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBDriver class methodsFor:'documentation'!

version_HG

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