Skip to content

Commit

Permalink
Update tags for variable nodes [feenkcom/gtoolkit#4146]
Browse files Browse the repository at this point in the history
  • Loading branch information
chisandrei committed Nov 5, 2024
1 parent 0e7fde0 commit 7e15b99
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 54 deletions.
46 changes: 23 additions & 23 deletions src/GToolkit-Pharo-Coder-Method/GtPharoMethodCoder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -220,15 +220,6 @@ GtPharoMethodCoder >> compile [
^ self compileInContext: self evaluationContext
]

{ #category : #accessing }
GtPharoMethodCoder >> compiledMethod [
<return: #CompiledMethod or: nil>

^ self existsInTheSystem
ifTrue: [ self behavior >> self selector ]
ifFalse: [ nil ]
]

{ #category : #'api - actions' }
GtPharoMethodCoder >> compileInContext: aGtPharoSourceCoderEvaluationContext [
"Try to compile the current source code and return true if it was successful, false otherwise"
Expand Down Expand Up @@ -259,6 +250,15 @@ GtPharoMethodCoder >> compileInContext: aGtPharoSourceCoderEvaluationContext [
^ true
]

{ #category : #accessing }
GtPharoMethodCoder >> compiledMethod [
<return: #CompiledMethod or: nil>

^ self existsInTheSystem
ifTrue: [ self behavior >> self selector ]
ifFalse: [ nil ]
]

{ #category : #'api - ast' }
GtPharoMethodCoder >> computeAst: theSourceString [
^ GtPharoParser
Expand Down Expand Up @@ -535,20 +535,6 @@ GtPharoMethodCoder >> forExample: anExampleWithResult [
self example: anExampleWithResult
]

{ #category : #accessing }
GtPharoMethodCoder >> formatWithRequesterObject: aRequester [
| ast |
ast := [ RBParser parseMethod: self currentSourceString ]
on: SyntaxErrorNotification
do: [ :ex |
^ self
notifyParseError: ex errorMessage
at: ex location
requesterObject: aRequester ].

self currentSourceString: ast formattedCode
]

{ #category : #initialize }
GtPharoMethodCoder >> forMethod: aCompiledMethod [
self methodBehavior:(GtPharoCoderBehavior explicit: aCompiledMethod methodClass).
Expand All @@ -571,6 +557,20 @@ GtPharoMethodCoder >> forMethod: aCompiledMethod in: aBehavior [
self protocol: aCompiledMethod category
]

{ #category : #accessing }
GtPharoMethodCoder >> formatWithRequesterObject: aRequester [
| ast |
ast := [ RBParser parseMethod: self currentSourceString ]
on: SyntaxErrorNotification
do: [ :ex |
^ self
notifyParseError: ex errorMessage
at: ex location
requesterObject: aRequester ].

self currentSourceString: ast formattedCode
]

{ #category : #'gt-extensions' }
GtPharoMethodCoder >> gtDiffViewFor: aView [
"<gtView>
Expand Down
51 changes: 27 additions & 24 deletions src/GToolkit-Pharo-Coder-Method/GtPharoMethodContextCoder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -25,20 +25,6 @@ GtPharoMethodContextCoder >> close [
self updateSelection"
]

{ #category : #accessing }
GtPharoMethodContextCoder >> compiledMethod [

"The context coder should allways return the compiled method from the context
as the method from the class can be changed. In that case the context will
use its own method."

^ context compiledCode method

"^ context isBlockContext
ifTrue: [ context home compiledCode ]
ifFalse: [ context compiledCode ]"
]

{ #category : #'api - actions' }
GtPharoMethodContextCoder >> compileInContext: aGtPharoSourceCoderEvaluationContext [
| withoutErrors compiledSuccesfully |
Expand Down Expand Up @@ -67,6 +53,20 @@ GtPharoMethodContextCoder >> compileInContext: aGtPharoSourceCoderEvaluationCont
^ withoutErrors and: [ compiledSuccesfully ]
]

{ #category : #accessing }
GtPharoMethodContextCoder >> compiledMethod [

"The context coder should allways return the compiled method from the context
as the method from the class can be changed. In that case the context will
use its own method."

^ context compiledCode method

"^ context isBlockContext
ifTrue: [ context home compiledCode ]
ifFalse: [ context compiledCode ]"
]

{ #category : #accessing }
GtPharoMethodContextCoder >> context [
<return: #Context>
Expand All @@ -82,7 +82,7 @@ GtPharoMethodContextCoder >> currentContext [
{ #category : #'accessing variables' }
GtPharoMethodContextCoder >> debuggerVariableNodes [
| variablesList |

variablesList := OrderedCollection new.
self instanceVariableNodesDo: [ :aNode | variablesList add: aNode ].
self temporaryVariableNodesDo: [ :aNode | variablesList add: aNode ].
Expand All @@ -91,11 +91,14 @@ GtPharoMethodContextCoder >> debuggerVariableNodes [
variablesList sort: [:node1 :node2 | node1 key < node2 key].
variablesList
addFirst: (GtInspectorSelfNode hostObject: self receiver);
addLast: (GtInspectorDynamicNode hostObject: self context label: 'thisContext' value: self context).
addLast: (GtInspectorDynamicNode
hostObject: self context
label: 'thisContext'
value: self context
tag: 'stack').
self stackVariableNodesDo: [ :aNode | variablesList add: aNode ].
^ variablesList


^ variablesList
]

{ #category : #accessing }
Expand Down Expand Up @@ -145,7 +148,7 @@ GtPharoMethodContextCoder >> instanceVariableNamesAndValuesDo: aBlock [

{ #category : #'accessing variables' }
GtPharoMethodContextCoder >> instanceVariableNodesDo: aBloc [
self receiver class allSlots collect: [ :aSlot |
self receiver class allSlots do: [ :aSlot |
aBloc value: (GtInspectorSlotNode
hostObject: self receiver
slot: aSlot) ]
Expand Down Expand Up @@ -270,7 +273,8 @@ GtPharoMethodContextCoder >> stackVariableNodesDo: aBlock [
(stackPosition > 0
ifTrue: [ ' - ' , stackPosition printString ]
ifFalse: [ '' ]))
value: (self context at: i)).
value: (self context at: i)
tag: 'stack').
stackPosition := stackPosition + 1 ]
]

Expand Down Expand Up @@ -330,10 +334,9 @@ GtPharoMethodContextCoder >> updateSourceFromContext [
{ #category : #'accessing variables' }
GtPharoMethodContextCoder >> workspaceDoItNodesDo: aBloc [
self context gtDebuggerDoItBindings do: [:aBinding |
aBloc value: ((GtInspectorDynamicNode
aBloc value: (GtInspectorDynamicNode
hostObject: self context
label: aBinding key
value: aBinding value)
variableTag: 'temp';
yourself) ]
value: aBinding value
tag: 'temporary') ]
]
Original file line number Diff line number Diff line change
Expand Up @@ -24,13 +24,6 @@ GtPharoSourceCoderEvaluationContext >> bindingOf: aSymbol [
^ self bindingStrategy bindingOf: aSymbol
]

{ #category : #accessing }
GtPharoSourceCoderEvaluationContext >> bindings [
<return: #TGtVariablesBindings>

^ bindingStrategy
]

{ #category : #accessing }
GtPharoSourceCoderEvaluationContext >> bindingStrategy [
<return: #TGtVariablesBindings>
Expand All @@ -47,6 +40,13 @@ GtPharoSourceCoderEvaluationContext >> bindingStrategy: aGtBindingStrategy [
bindingStrategy := aGtBindingStrategy
]

{ #category : #accessing }
GtPharoSourceCoderEvaluationContext >> bindings [
<return: #TGtVariablesBindings>

^ bindingStrategy
]

{ #category : #hack }
GtPharoSourceCoderEvaluationContext >> correctFrom: fromIndex to: toIndex with: aString [
NonInteractiveTranscript stdout
Expand Down

0 comments on commit 7e15b99

Please sign in to comment.