VDBVariableObject.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Fri, 06 Sep 2019 02:30:16 +0100
changeset 183 91a467093d63
parent 178 5d1c3e5fab6b
child 184 649f53564122
permissions -rw-r--r--
Fix `VDBStackApplication >> delayedUpdateAfterThreadStopped:` ...so stopped frame is pre-selected as default. This commit essentially undo the change done in 364ebdd1d42c: Generalize `VDBInstructionListView`

"{ Encoding: utf8 }"

"
jv:vdb - Visual / VM Debugger
Copyright (C) 2015-now Jan Vrany

This software is licensed under 'Creative Commons Attribution-NonCommercial 4.0 International License'

You may find a full license text in LICENSE.txt or at http://creativecommons.org/licenses/by-nc/4.0/
"
"{ Package: 'jv:vdb' }"

"{ NameSpace: Smalltalk }"

GDBVariableObject subclass:#VDBVariableObject
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'VDB-Core'
!

!VDBVariableObject class methodsFor:'documentation'!

copyright
"
jv:vdb - Visual / VM Debugger
Copyright (C) 2015-now Jan Vrany

This software is licensed under 'Creative Commons Attribution-NonCommercial 4.0 International License'

You may find a full license text in LICENSE.txt or at http://creativecommons.org/licenses/by-nc/4.0/
"
! !

!VDBVariableObject class methodsFor:'utilities'!

evaluate: expression in: frame using: debugger
    "Evaluates passed `expression` (in target language). If
     `frame` (as `GDBFrame`) is given, evaluate expression in
     context of that `frame`.

     Returns the result as `VDBVariableObject`."

    | result varobj |

    frame notNil ifTrue:[
        result := debugger send: (VDBMI_vdb_var_create new arguments: (Array with: '--thread' with: frame thread id with: '--frame' with: frame level with: '-' with: '*' with: expression)).
    ] ifFalse:[
        result := debugger send: (VDBMI_vdb_var_create new arguments: (Array with: '-' with: '*' with: expression)).
    ].
    varobj := result propertyAt: #result.
    varobj 
        setDebugger: debugger; 
        setExpression: expression;
        setFrame: frame;
        registerForFinalization. 
    ^ varobj

    "Created: / 06-07-2019 / 01:04:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBVariableObject methodsFor:'accessing'!

children
    self isValid ifFalse:[ ^ #() ].
    children isNil ifTrue:[ 
        (self isValid and:[has_more or:[ numchild isNil or:[numchild > 0]]]) ifTrue:[
            | result |

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

    "Created: / 06-07-2019 / 00:39:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2019 / 15:56:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

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'

    "

    "/ Raise an error early when #path is requested for a child of dynamic
    "/ varobj. Thie is not supported by GDB.
    "/ 
    "/ Although GDB should report an error [1], dur to a bug it report
    "/ either wrong (nonsense) value or crashes. A patch has been send
    "/ to the upstream [2], but meanwhile, check here as well in case someone
    "/ uses this with older / not yet patches version of GDB.
    "/ 
    "/ [1]: https://sourceware.org/gdb/onlinedocs/gdb/GDB_002fMI-Variable-Objects.html
    "/ [2]: https://sourceware.org/ml/gdb-patches/2018-06/msg00058.html
    "/ 
    (parent notNil and:[parent isDynamic]) ifTrue:[ 
        GDBError signal: 'Invalid varobj, #path is not supported for children of a dynamic varobjs'.
        ^ self
    ].

    path isNil ifTrue:[ 
        | result |

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

    "Created: / 06-07-2019 / 00:40:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2019 / 15:56:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

valueFormatted: aGDBOutputFormat
    "Return the value formatted using given format (as String)

    Supported formats are:
        * FormatSignedDecimal
        * FormatHexadecimal
        * FormatOctal
        * FormatPaddedHexadecimal

    To get the value in 'natural' format use plain #value 
    rather than #valueFormatted:
    "

    | format result |

    aGDBOutputFormat == FormatBinary ifTrue:[ 
        format := 'binary'
    ] ifFalse:[aGDBOutputFormat == FormatSignedDecimal ifTrue:[ 
        format := 'decimal'
    ] ifFalse:[aGDBOutputFormat == FormatHexadecimal ifTrue:[ 
        format := 'hexadecimal'
    ] ifFalse:[aGDBOutputFormat == FormatOctal ifTrue:[ 
        format := 'octal'
    ] ifFalse:[aGDBOutputFormat == FormatPaddedHexadecimal ifTrue:[ 
        format := 'zero-hexadecimal'
    ] ifFalse:[ 
        GDBError signal: 'Unsupported format: ', aGDBOutputFormat displayString  
    ]]]]].

    result := debugger send: (self commandVarEvaluateExpression arguments: (Array with: '-f' with: format with: name)).
    ^ result value

    "Created: / 06-07-2019 / 00:40:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

visualizer: aString
    "Set a visualizer for the variable object. `aString` is the 
     visualizer to use. The special value ‘None’ means to disable 
     any visualizer in use.

     If not ‘None’, `aString` must be a Python expression. This expression 
     must evaluate to a callable object which accepts a single argument.

     See https://sourceware.org/gdb/onlinedocs/gdb/GDB_002fMI-Variable-Objects.html
    "
    |result |

    self assert: (debugger isPrettyPrintingEnabled or:[ aString = 'None' ]).
    self visualizer = aString ifTrue:[ 
        "/ Already set, no need to do anything.    
        ^ self 
    ].
    result := debugger send: (VDBMI_vdb_var_set_visualizer arguments: (Array with: name with: aString)) andWait: true.
    result isDone ifTrue:[ 
        visualizer := aString.
        "/ Since we have changed the visualizer, children 
        "/ may have changed too. Delete them and recreate 
        "/ them on demand (see #children)
        numchild := nil.
        children notNil ifTrue:[ 
            children do:[:child | child release ].
            children := nil.  
        ].
    ].

    "Created: / 06-07-2019 / 00:41:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBVariableObject methodsFor:'copying'!

duplicate
    "Create and returns a duplicate of the receiver, representing
     the same value. Other than that the returned duplicate is completely 
     independent"

    | result varobj |

    result := debugger send: (VDBMI_vdb_var_duplicate arguments: (Array with: name)).
    varobj := result propertyAt: #result.
    varobj 
        setDebugger: debugger; 
        setExpression: self expression;
        setFrame: self frame;
        registerForFinalization. 
    ^ varobj

    "Created: / 06-07-2019 / 00:45:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2019 / 16:52:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!VDBVariableObject methodsFor:'updating'!

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

    debugger isNil ifTrue:[ 
        changed := false.
        ^ false.
    ].

    "/ If the thread is running, we cannot check for updates...
    (frame notNil and:[frame thread isRunning]) ifTrue:[
        ^ false
    ].    

    (self thread notNil and:[ self thread isValid not]) ifTrue:[ 
        self release.
        ^ true
    ].

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

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

    "Created: / 06-07-2019 / 00:41:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-07-2019 / 15:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !