GDBLocalProcess.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 28 Jan 2019 14:56:14 +0000
changeset 173 02546d4fbe6d
parent 164 a16705f64a64
child 185 4e1be69b39ce
permissions -rw-r--r--
Fix frame of `GDBThreadSelectedEvent` if inferior is running When ifnferior is running at time we get `=thread-selected` event, we should at least make that frame kind of usable by fixing up it's debugger and thread. This allow clients to use (to some extent) event's frame without worring (too much) about these details.

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

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 }"

GDBProcess subclass:#GDBLocalProcess
	instanceVariableNames:'pid'
	classVariableNames:''
	poolDictionaries:''
	category:'GDB-Private'
!

!GDBLocalProcess class methodsFor:'documentation'!

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

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

documentation
"
    GDBLocalProcess is a specialization of GDBProcess that spawns a
    local GDB process on a host machine. Spawning a running of GDB
    process is ully managed by an (sub)instance of `GDBLocalProcess`
    Due to platform differences, there are concrete variants for 
    different platforms.

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]
        GDBStXUnixProcess
        GDBStXWindowsProcess
        GDBRemoteProcess

"
! !

!GDBLocalProcess class methodsFor:'instance creation'!

newWithCommand: command
    "Return a new local GDBLocalProcess suitable for this platform 
     using `command` to launch GDB.

     If `command` is nil, default configured command is used
     (See GDBProcess class >> gdbExecutable)
    "
    self == GDBLocalProcess ifTrue:[
        Smalltalk isSmalltalkX ifTrue:[
            OperatingSystem isUNIXlike ifTrue:[
                ^ GDBStXUnixProcess basicNew initializeWithCommand: command
            ].
            ^ GDBStXSimpleProcess basicNew initializeWithCommand: command
        ].
    ].
    ^ self basicNew initializeWithCommand: command


    "
     GDBProcess new release."

    "Created: / 12-12-2018 / 22:19:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBLocalProcess methodsFor:'accessing'!

id
    "Return a string identification of this GDBProcess. 
     Used for debugging purposes only."

    ^ pid

    "Created: / 19-10-2018 / 10:09:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-10-2018 / 06:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBLocalProcess methodsFor:'initialization & release'!

initialize
    "Initializes itself using default gdb command"

    self initializeWithCommand: nil

    "Created: / 12-12-2018 / 20:11:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-12-2018 / 22:17:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

initializeWithCommand: command
    "Initializes itself using `command` string to launch GDB. 
     If `command` is nil, default configured command is used
     (See GDBProcess class >> gdbExecutable)"

    self subclassResponsibility

    "Created: / 12-12-2018 / 20:11:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 12-12-2018 / 22:18:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

release
    (pid notNil and:[pid > 1]) ifTrue:[
        OperatingSystem sendSignal:(OperatingSystem sigTERM) to: pid.       
    ].

    "Created: / 20-10-2018 / 07:12:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBLocalProcess methodsFor:'private'!

command2argv: commandOrNil
    "Parse given `commandOrNil` string and return an array of tokens
     suitable for passing back to `exec()` family of functions.

     If `commandOrNil` is `nil`, then use default GDB command.
     On error, thrown GDBError.
    "

    | command argv exe |


    commandOrNil isNil ifTrue:[ 
        command := self class gdbCommand.
        command isEmptyOrNil ifTrue:[ 
            GDBError signal: 'GDB not found. Please set GDB command - `UserPreferences current gdbCommand:''...''`'.
            ^ nil.
        ].
    ] ifFalse:[ 
        command := commandOrNil.
        command isEmpty ifTrue:[ 
            GDBError signal: 'Command is empty'.
            ^ nil.
        ].
    ].
    argv := GDBShellCommandParser parse: command.
    exe := argv first.
    exe asFilename exists ifFalse:[ 
        "/ Try to find executable a long PATH, just as shell 
        "/ would do...
        exe := OperatingSystem pathOfCommand: exe.
        exe notNil ifTrue:[ 
            argv at:1 put: exe.
        ] ifFalse:[
            GDBError signal: 'Command not found: ', argv first.
            ^ nil
        ].
    ] ifTrue:[ 
        "/ `exe` points to real file (or directory...), so
        "/ check here...
        exe := exe asFilename.
        exe isExecutable ifTrue:[ 
            argv at:1 put: exe asAbsoluteFilename pathName.
        ] ifFalse:[ 
            GDBError signal: 'Command not executable: ', argv first.
            ^ nil
        ].
    ].
    ^ argv

    "Created: / 17-12-2018 / 10:48:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

exited: status
    "Called when spawn GDB process terminates for whatever reason"
    pid := nil.
    connection released: status

    "Created: / 20-06-2014 / 21:35:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-01-2018 / 21:50:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 17-10-2018 / 22:30:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !