GDBRegisterWithValue.st
author Jan Vrany <jan.vrany@labware.com>
Mon, 04 Sep 2023 14:00:57 +0100
changeset 314 4a2ef5a087f0
parent 272 cdd1c9ad00de
child 315 91819b724b59
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 }"

GDBDebuggerObject subclass:#GDBRegisterWithValue
	instanceVariableNames:'register frame valueString value changed previous'
	classVariableNames:''
	poolDictionaries:''
	category:'GDB'
!

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

!GDBRegisterWithValue class methodsFor:'accessing-magritte'!

descriptionContainer
    ^ super descriptionContainer
        define: #number as: Integer;
        define: #value as: String;
        yourself

    "Created: / 26-09-2018 / 10:38:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBRegisterWithValue methodsFor:'accessing'!

name
    ^  register name

    "Created: / 27-09-2018 / 10:06:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

number
    ^ register isInteger ifTrue:[
        register
    ] ifFalse:[
        register number
    ]

    "Created: / 27-09-2018 / 09:56:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

register
    "Return the register definition of this register (as GDBRegister)"
    ^ register

    "Modified (comment): / 24-03-2021 / 15:13:22 / Jan Vrany <jan.vrany@labware.com>"
!

value
    "Return the value of the register. The returned value is either

       * an integer in case the register is integer register - GPRs and so on)
       * a dictionary in case of 'composite' registers - for example a value
         of FPR might be returned as '{float = 0xABCDDCBA, double = 0xA...B}'
         Similarly for vector registers (SSE / SSE2 regs on x86, VSRs on POWER)
    "
    (value isNil or:[changed value]) ifTrue: [
        value := (GDBMIParser on: self valueString) parseValue.
        "/ Sigh, we do now know the 'type' of the register (that is,
        "/ GPR, FPR, SPR or some other kind. We do not even know the bitsize. 
        "/ Still, it is kinda handy to intepret GPRs as signed value.
        "/ 
        "/ However, #parseValue returns it as unsigned value, so we make
        "/ some guesses based on unsigned value.
        "/ 
        "/ First, assume it is 64bit unsigned value...
        (value between: 16r8000000000000000 and: 16rFFFFFFFFFFFFFFFF) ifTrue: [ 
            value := (value bitAnd:16rFFFFFFFFFFFFFFFF)-16r10000000000000000 
        ] ifFalse: [ 
            "/ ...then assume it is 32bit value...
            (valueString size == (2+8) and:[value between: 16r80000000 and: 16rFFFFFFFF]) ifTrue: [ 
                value := (value bitAnd:16rFFFFFFFF)-16r100000000 
            ].
        ].
    ].
    ^ value

    "Modified: / 27-09-2018 / 15:26:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-01-2022 / 16:22:39 / Jan Vrany <jan.vrany@labware.com>"
!

value: anObject
    "Set the value of register. Currently this is limited to integer registers
     only."

    self value isInteger ifFalse: [ 
        self error: 'Compound values not supported'.
    ].
    debugger 
        send: (GDBMI_data_evaluate_expression arguments: (Array with: '--thread' with: frame thread id with: '--frame' with: frame level with: ('$', register name , ' = ' , (anObject asInteger printString) )))
        andWithResultDo:[ :result |
            result isDone ifTrue: [
                frame invalidate: self.
                changed value: true.
                debugger push: (GDBRegisterValueChangedEvent new setRegister: self)
            ].
        ].

    "Created: / 10-09-2021 / 15:31:35 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 18-11-2021 / 12:13:34 / Jan Vrany <jan.vrany@labware.com>"
!

valueString
    valueString isNil ifTrue: [
        | result registers |

        frame isValid ifTrue: [
            [
                result := debugger send: (GDBMI_data_list_register_values new arguments: (Array with: '--thread' with: frame thread id with: '--frame' with: frame level with: 'r' with: register number)).
                registers := result propertyAt: #'register-values'.     
                self assert: registers size == 1.
                self assert: registers first register = register number.
                valueString := registers first valueString.
            ] on: GDBCommandFailedError do: [:ex |  
                valueString := ex description.
            ].
        ] ifFalse: [ 
            valueString := 'invalid frame'.
        ].
            (previous notNil and:[previous ~= valueString]) ifTrue: [ 
                changed value: true.
                debugger push: (GDBRegisterValueChangedEvent new setRegister: self)
            ].
    ] ifFalse: [
        changed value.
    ].
    ^ valueString

    "Created: / 10-09-2021 / 14:14:14 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 18-11-2021 / 18:03:18 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBRegisterWithValue methodsFor:'initialization'!

setDebugger: aGDBDebugger
    super setDebugger: aGDBDebugger.
    changed := GDBTransientDataHolder debugger: debugger factory: [
        (frame notNil and:[frame isValid]) ifTrue:[
            | changes change |

            changes := frame registersChanges.
            change := changes detect:[:each | each number = self number ] ifNone:[ nil ].
            (change notNil and:[change valueString ~= valueString]) ifTrue:[
                valueString := change valueString.
                value := nil.
                true
            ] ifFalse:[ 
                false
            ].
        ] ifFalse:[ 
            false
        ].
    ].

    "Created: / 27-09-2018 / 15:11:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 18-11-2021 / 17:19:20 / Jan Vrany <jan.vrany@labware.com>"
!

setFrame: aGDBFrame
    self setDebugger: aGDBFrame debugger.
    frame := aGDBFrame.

    "Created: / 26-09-2018 / 22:25:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 27-09-2018 / 15:31:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setRegisterFrom: aDictionary
    self assert: register isInteger.
    self assert: (aDictionary includesKey: register).

    register := aDictionary at: register.

    "Created: / 26-09-2018 / 10:41:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBRegisterWithValue methodsFor:'printing & storing'!

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

    super printOn:aStream.
    aStream nextPut:$(.
    register isInteger ifTrue:[
        register printOn:aStream.
    ] ifFalse:[ 
        register name printOn:aStream.    
    ].
    aStream nextPutAll: ': '.
    valueString printOn: aStream.
    aStream nextPut:$).

    "Modified: / 26-09-2018 / 10:48:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GDBRegisterWithValue methodsFor:'private'!

_number: anInteger
    register := anInteger

    "Created: / 26-09-2018 / 10:39:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

_value: aString
    valueString := aString

    "Created: / 10-09-2021 / 15:43:04 / Jan Vrany <jan.vrany@labware.com>"
!

invalidate
    valueString notNil ifTrue: [
        changed notNil ifTrue: [ changed invalidate ].
        previous := valueString.
        valueString := nil.
        value := nil.
    ].

    "Created: / 10-09-2021 / 15:37:58 / Jan Vrany <jan.vrany@labware.com>"
    "Modified: / 18-11-2021 / 17:48:07 / Jan Vrany <jan.vrany@labware.com>"
! !

!GDBRegisterWithValue methodsFor:'queries'!

hasChanged
    "Return true, if the value of this register has changed since last
     'stop', false otherwise (i.e., when unchanged)"

    ^ changed value

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

!GDBRegisterWithValue class methodsFor:'documentation'!

version_HG

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