GDBVariableObject.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Mon, 05 Feb 2018 21:45:22 +0000
changeset 107 7a315f1c9260
parent 106 12c96f17fc53
child 108 f34505ec6a7f
permissions -rw-r--r--
Variable objects: added `#path` returning an absolute expression to access the value in source langiage ...as opositte to `#expression` with return a parent-relative expression.

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

GDBDebuggerObject subclass:#GDBVariableObject
	instanceVariableNames:'parent name exp path thread frame value type numchild has_more
		children changed inScope'
	classVariableNames:''
	poolDictionaries:''
	category:'GDB-Core'
!

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

!GDBVariableObject class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

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

description
    ^ (super description)
        define:#name as:String;
        define:#numchild as:Integer;
        define:#value as:String;
        define:#type as:String;
        define:#'thread-id' as:Integer;
        define:#has_more as:Boolean;
        define:#dynamic as:Boolean;
        define:#displayhint as:String;
        yourself

    "Created: / 16-09-2014 / 23:59:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-02-2015 / 17:10:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'accessing'!

children
    self isValid ifFalse:[ ^ #() ].
    children isNil ifTrue:[ 
        self hasChildren ifTrue:[
            | result |

            result := debugger send: (GDBMI_var_list_children arguments: (Array with: '--all-values' with: name)).
            children := result propertyAt: #children.   
            children do:[:each | each setDebugger: debugger; setParent: self ].
        ] ifFalse:[ 
            children := #().
        ].
    ].
    ^ children

    "Created: / 27-01-2018 / 22:53:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-02-2018 / 10:07:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

expression
    "Return the expression in target language to access the value (asDtring)
     The expression is relative to it's direct parent (if any),

     For example, consider

         typedef struct _point {
            int x;
            int y;
         } point;
         ...
         point p1 = { 10, 20 };

     and consider a variable object `o` that represents `y` member of point 
     `p1`. Then:

        o path '/ -> 'p1.y'

    while

        p expression '/ -> 'y'
    "

    ^ exp

    "Created: / 28-01-2018 / 21:36:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 05-02-2018 / 21:16:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

id
    "Returns the GDB ID (name) of the variable object. This is
    used in commands to identify a variable object instance."

    ^ name

    "Created: / 28-01-2018 / 21:35:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

parent
    ^ parent
!

path
    "Return (absolute) expression in target language to access the value 
     (asDtring).

     For example, consider

         typedef struct _point {
            int x;
            int y;
         } point;
         ...
         point p1 = { 10, 20 };

     and consider a variable object `o` that represents `y` member of point 
     `p1`. Then:

        o path '/ -> 'p1.y'

    while

        p expression '/ -> 'y'

    "
    path isNil ifTrue:[ 
        | result |

        result := debugger send: (GDBMI_var_info_path_expression arguments: (Array with: name)).
        path := result propertyAt: #'path_expr'.
    ].
    ^ path

    "Created: / 05-02-2018 / 21:16:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

thread
    "
    If a variable object is bound to a specific thread, returns
    that thread (as GDBThread). Otherwise, `nil` is returned.
    "
    | threadId |
    thread isInteger ifTrue:[ 
        threadId := thread.
        thread := debugger threadForId: threadId.
    ].
    ^ thread

    "Created: / 04-02-2018 / 21:35:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2018 / 18:38:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

type
    ^ type
!

value
    changed value. "/ to force update if necessary
    self isValid ifFalse:[ ^ self class classResources string: '<invalid>' ].
    self inScope ifFalse:[ ^ self class classResources string: '<out-of-scope>' ].
    ^ value

    "Modified: / 12-02-2018 / 22:00:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'displaying'!

displayOn: aStream
    self displayOn: aStream indent: 0

    "Created: / 28-01-2018 / 21:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

displayOn: aStream indent: anInteger
    aStream next: anInteger * 4 put: Character space.
    aStream nextPutAll: exp; space; nextPut: $=; space.
    self hasChildren ifTrue:[ 
        aStream nextPut:${; cr.
        self children do:[:each | 
            each displayOn: aStream indent: anInteger + 1.
            aStream cr.
        ].
        aStream next: anInteger * 4 put: Character space; nextPut:$}.
    ] ifFalse: [ 
        aStream nextPutAll: value
    ].

    "Created: / 28-01-2018 / 21:42:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'finalization'!

executor
    ^ GDBVariableObjectExecutor new 
            setDebugger: debugger;
            setId: name;
            yourself

    "Created: / 28-01-2018 / 23:27:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

finalizationLobby
    self assert: debugger notNil.
    ^ debugger finalizationRegistry.

    "Created: / 28-01-2018 / 23:21:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'initialization & release'!

initialize
    "Invoked when a new instance is created."

    super initialize.
    inScope := true.

    "Modified: / 12-02-2018 / 22:07:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

release
    "Releases the variable object and all its children. Once released, 
     the variable object is invalid (i.e., `#isValid` would return `false`) 
     and should not be used anymore."

    self release: true

    "Created: / 04-02-2018 / 23:21:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-02-2018 / 09:37:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

release: delete
    "Releases the variable object and all its children. If 
     `delete` is `true`, send `-var-delete -c`."

    self assert: debugger notNil.
    self assert: (delete not or:[ parent isNil ]) description: 'Only top-level objects can be deleted (for now)'.

    "/ Release all children first, but not not 'delete' them 
    "/ in GDB (will be done later)
    children notEmptyOrNil ifTrue:[ 
        children do: [ :child | child release:false ].
    ].
    children := nil.
    changed := [ changed := false. true ]. 

    "/ Now 'delete' the variable and all its children
    "/ in GDB
    delete ifTrue:[ 
        self unregisterForFinalization.
        debugger isConnected ifTrue:[
            debugger send: (GDBMI_var_delete arguments: (Array with: '-c' with: name))
        ].
    ].

    "/ Finally, clear the debugger instvar (it's tested in
    "/ `#isValid`
    debugger := nil.

    "Created: / 13-02-2018 / 09:36:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setDebugger: aGDBDebugger
    super setDebugger: aGDBDebugger.
    aGDBDebugger notNil ifTrue:[
        changed := GDBTransientDataHolder debugger: debugger factory: [ self updateChanged ].
    ].

    "Created: / 01-02-2018 / 09:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setExpression: aString
    exp := aString

    "Created: / 28-01-2018 / 21:39:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setParent: variableObjectOrNil
    self assert: (variableObjectOrNil isNil or:[ variableObjectOrNil isKindOf: self class ]).
    self assert: debugger notNil.

    "Created: / 27-01-2018 / 22:54:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 01-02-2018 / 09:29:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

thread_id: anInteger
    thread := anInteger

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


!GDBVariableObject methodsFor:'printing & storing'!

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

    super printOn:aStream.
    aStream nextPutAll:'('.
    value printOn: aStream.
    aStream nextPutAll:')'.

    "Created: / 13-06-2017 / 17:03:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'queries'!

hasChanged
    ^ changed value

    "Created: / 30-01-2018 / 00:27:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-02-2018 / 22:16:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hasChildren
    ^ self isValid and:[numchild > 0 ]

    "Created: / 27-01-2018 / 22:47:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-02-2018 / 22:09:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'testing'!

inScope
   changed value. "/ to force update if necessary
    ^ inScope

    "Created: / 12-02-2018 / 21:56:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isValid
    changed value. "/ to force update if necessary
    ^ debugger notNil

    "Created: / 04-02-2018 / 21:33:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2018 / 22:28:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject methodsFor:'updating'!

updateChanged
    "Check for updates and update all changed variables accordingly."

    debugger isNil ifTrue:[ 
        changed := false.
        ^ false.
    ].
    (self thread notNil and:[ self thread isValid not]) ifTrue:[ 
        self release.
        ^ true
    ].

    parent notNil ifTrue:[ 
        parent updateChanged
    ] ifFalse:[
        | result changelist |

        result := debugger send: (GDBMI_var_update arguments: (Array with: '--all-values' with: name)).
        changelist := result propertyAt: #changelist.
        self updateChanged: changelist.        
    ].
    ^ false

    "Created: / 30-01-2018 / 01:08:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2018 / 23:09:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

updateChanged: changelist
    | change |

    changelist isEmptyOrNil ifTrue:[ ^ self ].
    change := changelist detect: [ :each | each id = self id ] ifNone:[nil].
    change notNil ifTrue:[ 
        value := change value.
        inScope := change inScope.
        inScope = 'invalid' ifTrue:[ 
            self release.
            ^ self.
        ].
        changed value: true.
        changelist remove: change.
        changelist isEmptyOrNil ifTrue:[ ^ self ].
    ] ifFalse:[ 
        changed value: false.
    ].
    children notEmptyOrNil ifTrue:[ 
        children do: [ :each | each updateChanged: changelist ]
    ].

    "Created: / 30-01-2018 / 01:09:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 12-02-2018 / 22:29:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBVariableObject class methodsFor:'documentation'!

version_HG

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