Skip to content

Commit

Permalink
Adds linked probes at right intervals and deletes them properly
Browse files Browse the repository at this point in the history
  • Loading branch information
JoeAtHPI committed Oct 5, 2023
1 parent 0a4c68a commit fd09757
Show file tree
Hide file tree
Showing 32 changed files with 135 additions and 91 deletions.

This file was deleted.

Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ compileCue: aCueWithStyledSource noPattern: aBoolean ifFail: failBlock
inside the morph to re-fullfill that premise again during compilation."
| originalMethodNode bpUnstyledSource unstyledCue |
bpUnstyledSource := aCueWithStyledSource sourceStream contents asString.

unstyledCue := CompilationCue
source: bpUnstyledSource readStream
context: aCueWithStyledSource context
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,15 +11,7 @@ compileInstrumentedVersionOf: aCue
ifTrue: [
self backgroundCompileInstrumentedVersionOf: aCue basedOn: parseResult.
^ true]
ifFalse: [
"das oben schlägt fehl, weil er keine methoddeclaration findet"
"hier ist die cue kaputt, weil er keine class zuweisen kann. doch nochmal
ne andere compile version, die speziell für editclass zurechtgeschnitten ist?"
parseResult := PEGParserBPSmalltalk new
match: originalCode
startingFrom: #KeywordMessageSend.
parseResult succeeded ifTrue: [self backgroundCompileInstrumentedVersionOf: aCue basedOn: parseResult.
^ true] ifFalse: [^false]].
ifFalse: [^ false].



Expand Down

This file was deleted.

Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
private
rewriteToSource: parseResult

^ self rewriter value: parseResult
Original file line number Diff line number Diff line change
Expand Up @@ -6,12 +6,10 @@
"instance" : {
"annotationKeywords" : "pre 11/8/2019 20:29",
"backgroundCompileInstrumentedVersionOf:basedOn:" : "pre 10/12/2020 15:36",
"backgroundCompileInstrumentedVersionOf:basedOn:noPattern:" : "joabe 9/26/2023 16:07",
"compileCue:noPattern:ifFail:" : "joabe 9/27/2023 16:14",
"compileInstrumentedVersionOf:" : "joabe 9/22/2023 23:28",
"compileInstrumentedVersionOf:noPattern:" : "joabe 9/26/2023 15:54",
"compileCue:noPattern:ifFail:" : "joabe 10/2/2023 12:53",
"compileInstrumentedVersionOf:" : "jb 9/9/2021 17:31",
"keywords" : "pre 11/30/2022 09:33",
"methodSourceRequiresBPLayers:" : "pre 11/11/2019 15:49",
"parse:" : "pre 5/3/2021 15:01",
"rewriteToSource:" : "pre 8/17/2020 08:54",
"rewriteToSource:" : "joabe 10/2/2023 12:48",
"rewriter" : "jb 12/7/2020 18:03" } }
Original file line number Diff line number Diff line change
Expand Up @@ -7,9 +7,12 @@ rewriteAssignmentNode: aNode withTag: aTag
^ annotationInformation isProbe
ifFalse: [self rewriteNode: aNode withTag: aTag]
ifTrue: ["To handle assignment probes"
annotationInformation := annotationInformation asAssignmentProbe.
"The following is a hack to some degree, but a separate semantic would be overkill here"
variableNames := aNode children first "NormalStatement" children first "AssignmentOperation*" children collect: [:assignment |
assignment children first interval contents].
annotationInformation := annotationInformation asAssignmentProbe.
variableNames := (aNode children first ruleName = #AnnotatedStatement)
ifTrue: [ "Nested assignments" #()]
ifFalse: ["The following is a hack to some degree, but a separate semantic would be overkill here"
aNode children first "NormalStatement"
children first "AssignmentOperation*"
children collect: [:assignment |assignment children first interval contents]] .
annotationInformation variableNames: variableNames.
annotationInformation instrumentationCallFor: (self value: aNode)]
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@
"nextBlockId" : "pre 1/27/2020 09:17",
"nextProbeId" : "pre 5/10/2019 12:20",
"rewriteArgumentNode:withTag:" : "pre 7/23/2022 15:41",
"rewriteAssignmentNode:withTag:" : "pre 7/6/2020 18:10",
"rewriteAssignmentNode:withTag:" : "joabe 10/4/2023 15:31",
"rewriteCascadeNode:withTag:" : "pre 4/29/2020 17:05",
"rewriteNode:withTag:" : "pre 9/25/2020 11:20",
"value:" : "pre 9/25/2020 11:42",
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
initialize-release
removeFromMethod: aCompiledMethod

"Intended to delete annotations from outside a browser"
"Intended to delete annotations but not the enclosed expression from outside a browser"
aCompiledMethod bpAnnotations
detect: [:anAnnotation | anAnnotation id = self id ]
ifFound: [:theAnnotationToRemove | | text startOfTag expressionStart replacementStart replacementEnd |
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@
"morphClass" : "jb 3/5/2022 12:54",
"otherInformation" : "pre 5/29/2019 10:59",
"otherInformation:" : "jb 12/7/2020 18:06",
"removeFromMethod:" : "jb 1/10/2022 19:20",
"removeFromMethod:" : "joabe 10/5/2023 17:28",
"startTag" : "pre 5/10/2021 09:44",
"startTagSource" : "jb 12/7/2020 18:06",
"startTagSource:" : "pre 5/29/2019 10:59",
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
initialize-release
deleteLinkedProbes

| browser |
browser := BPBrowser open.
self linkedProbes do: [:aProbe |
browser browseReference: aProbe methodReference.
browser removeAnnotations: {aProbe}].

browser currentWindow delete.
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
initialize-release
initialize

super initialize.

linkedProbes := OrderedCollection new.
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
as yet unclassified
serialization
instrumentationCallFor: actualEnclosedExpressionSource

^ '(self bpTraceVariable: [{1}] forProbe: {2} inContext: thisContext)'
format: {actualEnclosedExpressionSource . self id}
^ '(self bpTraceVariable: [{1}] forProbe: {2} linked: \{{3}\} inContext: thisContext)'
format: {actualEnclosedExpressionSource .
self id.
((self linkedProbes gather: [:probe | probe id]) joinSeparatedBy: ' . ')}
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
linkedProbes

^ linkedProbes
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
as yet unclassified
serialization
probeTypeTag

^ 'bpInstanceProbe'
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
as yet unclassified
initialize-release
removeFromMethod: aCompiledMethod

"do nothing"
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,11 @@
"assignedClassName" : "joabe 9/28/2023 15:45",
"assignedClassName:" : "joabe 9/28/2023 15:46",
"canBeAnnotatedTo" : "joabe 9/21/2023 21:08",
"instrumentationCallFor:" : "joabe 9/25/2023 18:43",
"deleteLinkedProbes" : "joabe 10/5/2023 17:34",
"initialize" : "joabe 10/4/2023 15:33",
"instrumentationCallFor:" : "joabe 10/4/2023 15:37",
"isInstanceVariableProbe" : "joabe 9/21/2023 21:18",
"linkedProbes" : "joabe 10/4/2023 15:33",
"probeTypeTag" : "joabe 9/25/2023 17:30",
"removeFromMethod:" : "joabe 9/27/2023 16:43",
"variableName" : "joabe 9/28/2023 14:47",
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@
],
"commentStamp" : "",
"instvars" : [
"assignedClassName" ],
"assignedClassName",
"linkedProbes" ],
"name" : "BPInstanceVariableProbe",
"pools" : [
],
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
*Babylonian-Core
bpExtractVariableAssignmentRangesNamed: aVariableName

^ (self extractAssignmentIntervalsFrom: self parseTree named: aVariableName) flatten


Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
*Babylonian-Core
extractAssignmentIntervalsFrom: aRBNodeWithBody named: aVariableName

"Private"
| currentIntervals nestedIntervals |
"No shadowing"
((aRBNodeWithBody body temporaries collect: [:aVariableNode | aVariableNode token value])
includes: aVariableName) ifTrue: [^ #()].

nestedIntervals := aRBNodeWithBody body statements select: [:aRBNode | aRBNode isBlock]
thenCollect: [:aBlockNode | self extractAssignmentIntervalsFrom: aBlockNode named: aVariableName].
currentIntervals := aRBNodeWithBody body statements select: [:aRBNode |
aRBNode isAssignment and: [aRBNode variable token value = aVariableName]]
thenCollect: [:anAssignmentNode |
anAssignmentNode startWithoutParentheses@anAssignmentNode stopWithoutParentheses].

^ currentIntervals, nestedIntervals


Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,12 @@
"bpActiveExamples" : "pre 8/20/2020 15:51",
"bpAnnotations" : "pre 6/24/2021 14:26",
"bpExamples" : "pre 1/11/2023 15:01",
"bpExtractVariableAssignmentRangesNamed:" : "joabe 10/4/2023 14:47",
"bpNewExampleFrom:" : "pre 5/10/2021 09:11",
"bpRemoveExample:" : "pre 5/19/2021 21:35",
"compiledMethod" : "pre 7/7/2020 15:39",
"exampleInstanceName" : "pre 9/28/2021 16:22",
"extractAssignmentIntervalsFrom:named:" : "joabe 10/4/2023 14:21",
"isBPInstalled" : "pre 1/11/2021 12:00",
"isExampleInstanceMethod" : "pre 9/28/2021 16:00",
"newExampleInstance" : "pre 9/28/2021 16:00" } }
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
as yet unclassified
removeButtonClicked

"LSP violation here - but otherwise the removal of the morph won't happen... -jb"
self annotation deleteLinkedProbes.

BPClassNameToInstanceProbes value removeProbe: self annotation.
super removeButtonClicked.

self containingBrowser removeAnnotations: {self annotation}.



Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ as yet unclassified
step

| newTraces tracesChanged |
self resetHeight.
"self resetHeight."

"newTraces := self getTraces asIdentitySet.
tracesChanged := newTraces ~= displayedTraces.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,5 +2,5 @@
"class" : {
},
"instance" : {
"removeButtonClicked" : "joabe 9/28/2023 15:54",
"step" : "joabe 9/25/2023 18:34" } }
"removeButtonClicked" : "joabe 10/4/2023 16:22",
"step" : "joabe 10/4/2023 11:52" } }
Original file line number Diff line number Diff line change
Expand Up @@ -12,11 +12,13 @@ determineIntervalOfVariableNameIn: anInterval having: aTopologicalCollectionOfAn
selectedText := (self contents atAll: anInterval) withBlanksTrimmed.
self flag: #todo. "wenn es sowas wie aha und aha2 gibt, dann wird das falsch sein, wenn ich aha markiere
und aha2 als erstes kommt"
"restliches todo: test schreiben"

^ self selectedClassOrMetaClass instVarNames
detect: [:aVariable | aVariable = selectedText]
ifFound: [:matchingVariable | | start |
start := self contents findString: matchingVariable.
^ Interval from: start to: start + matchingVariable size - 1]
ifFound: [:matchingVariable | | interval |
"in case we have variables like 'foo2' and 'foo' we have to consider spaces or '' too"
interval := (self contents allRangesOfRegexMatches: '(''| )', matchingVariable, '(''| )') first.
^ Interval from: (interval start + 1) to: (interval stop - 1)]


Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@ determineMessageSendNodeIn: anInterval

| nodes messageSendRuleNames lowestMessageSend |
self bpEnsureContentsAndSelectedMessage.
self flag: #todo. "will break for instance probes jb"
nodes := currentCompiledMethod bpSourceMap at: anInterval start.
messageSendRuleNames := #(ExpressionOperandCascade ExpressionUnaryCascade ExpressionBinaryCascade UnaryMessageSend BinaryMessageSend KeywordMessageSend).
^ lowestMessageSend := nodes reversed
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -6,5 +6,6 @@ doAddAnnotation: anAnnotation in: interval
actualInterval ifNil: [self codeTextMorph textMorph flash. ^ self].

anAnnotation isInstanceVariableProbe
ifTrue: [self doAddInstanceProbeToRegistry: anAnnotation nameIn: actualInterval]
ifTrue: [self doAddInstanceProbeToRegistry: anAnnotation nameIn: actualInterval.
self doAddLinkedAnnotationsFor: anAnnotation]
ifFalse: [self doAddAnnotationMorphToMethod: anAnnotation in: actualInterval].
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
doAddInstanceProbeToRegistry: anInstanceVariableProbe nameIn: anInterval

anInstanceVariableProbe
variableName: (self codeTextMorph text atAll: anInterval);
variableName: (self codeTextMorph text atAll: anInterval) asString;
assignedClassName: (self selectedClass name).
BPClassNameToInstanceProbes value addProbe: anInstanceVariableProbe

Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
*Babylonian-UI-private
doAddLinkedAnnotationsFor: anInstanceVariableProbe

| allSenderMethods |
allSenderMethods := (self systemNavigation
allAccessesTo: anInstanceVariableProbe variableName
from: (Smalltalk bindingOf: (anInstanceVariableProbe assignedClassName asSymbol)) value).

allSenderMethods collect: [:aMethodReference | self doAddLinkedAnnotationsFor: anInstanceVariableProbe in: aMethodReference].
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
*Babylonian-UI-private
doAddLinkedAnnotationsFor: anInstanceVariableProbe in: aMethodReference

| allRanges styledText |
allRanges := aMethodReference compiledMethod bpExtractVariableAssignmentRangesNamed: anInstanceVariableProbe variableName.
styledText := aMethodReference sourceCode.

allRanges do: [:aRange | anInstanceVariableProbe linkedProbes add:
(self styleText: styledText in: aRange referencing: aMethodReference)].

allRanges ifNotEmpty: [SystemChangeNotifier uniqueInstance doSilently:
[aMethodReference actualClass
compile: (BPStyler new unstyledTextFrom: styledText)
classified: aMethodReference category]].
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
*Babylonian-UI-private
styleText: aText in: aRange referencing: aMethodReference

| linkedProbe |
self flag: #todo. "If assignment already has an annotation, re-use that one"
linkedProbe := BPProbe new methodReference: aMethodReference.
aText addAttribute: (
BPTextDecoration new
anchoredMorph: linkedProbe asMorph;
yourself)
from: aRange x
to: aRange y.
^ linkedProbe

0 comments on commit fd09757

Please sign in to comment.