Skip to content

Commit

Permalink
Adds global dict to keep track of probes
Browse files Browse the repository at this point in the history
  • Loading branch information
JoeAtHPI committed Sep 28, 2023
1 parent e47ec04 commit 8c847c6
Show file tree
Hide file tree
Showing 44 changed files with 268 additions and 33 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
private
backgroundCompileInstrumentedVersionOf: aCue basedOn: parseResult noPattern: aBoolean

| instrumentedResult newCode |
self halt.
newCode := self rewriteToSource: parseResult.
SystemChangeNotifier uniqueInstance doSilently: [
"Wann ist aCue getClass compile nicht mit BPCompiler?"
instrumentedResult :=
aCue getClass newCompiler compileCue: (CompilationCue
source: newCode
class: aCue getClass
environment: aCue environment
requestor: nil)
noPattern: aBoolean
ifFail: [^nil] ].
"instrumentedResult := aCue getClass compile: newCode]."

Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,11 @@ compileCue: aCueWithStyledSource noPattern: aBoolean ifFail: failBlock
source: bpUnstyledSource readStream
context: aCueWithStyledSource context
receiver: aCueWithStyledSource receiver
class: aCueWithStyledSource getClass
class: aCueWithStyledSource getClass
environment: aCueWithStyledSource environment
requestor: aCueWithStyledSource requestor.
originalMethodNode := super compileCue: unstyledCue noPattern: aBoolean ifFail: failBlock.

bpUnstyledSource := originalMethodNode sourceText asString.
(self methodSourceRequiresBPLayers: bpUnstyledSource) ifTrue: [
(self compileInstrumentedVersionOf: aCueWithStyledSource) ifFalse: failBlock].
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,15 @@ compileInstrumentedVersionOf: aCue
ifTrue: [
self backgroundCompileInstrumentedVersionOf: aCue basedOn: parseResult.
^ true]
ifFalse: [^ false].
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]].



Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
private
compileInstrumentedVersionOf: aCue noPattern: aBoolean

| originalCode parseResult startingFrom |
"We do not serialize the examples into the instrumented method as
they only 'live' in the base method."
originalCode := aCue sourceStream contents asBPSourceWithoutExamples.
startingFrom := aBoolean
ifFalse: [#MethodDeclaration]
ifTrue: [#KeywordMessageSend].

parseResult := PEGParserBPSmalltalk new
match: originalCode
startingFrom: startingFrom.

parseResult succeeded
ifTrue: [
self
backgroundCompileInstrumentedVersionOf: aCue
basedOn: parseResult
noPattern: aBoolean.
^ true]
ifFalse: [^false].




Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,10 @@
"instance" : {
"annotationKeywords" : "pre 11/8/2019 20:29",
"backgroundCompileInstrumentedVersionOf:basedOn:" : "pre 10/12/2020 15:36",
"compileCue:noPattern:ifFail:" : "pre 7/20/2022 16:41",
"compileInstrumentedVersionOf:" : "jb 9/9/2021 17:31",
"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",
"keywords" : "pre 11/30/2022 09:33",
"methodSourceRequiresBPLayers:" : "pre 11/11/2019 15:49",
"parse:" : "pre 5/3/2021 15:01",
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
grammar rules
AnnotatedKeywordMessageSend: aNode startTag: startTag actualMessage: message endTag: endTag

^ self rewriteNode: message withTag: startTag
^ self rewriteNode: message withTag: startTag
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
as yet unclassified
rewrite rules
bpTemporaryProbe: annotation with: originalExpressionSourceNode

^ annotation instrumentationCallFor: (self value: originalExpressionSourceNode)
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
"AnnotatedBinaryMessageSend:startTag:actualMessage:endTag:" : "pre 3/5/2020 16:30",
"AnnotatedBlockLiteral:startTag:actualBlock:endTag:" : "pre 9/1/2022 20:34",
"AnnotatedExpression:startTag:actualExpression:endTag:" : "pre 1/24/2020 17:26",
"AnnotatedKeywordMessageSend:startTag:actualMessage:endTag:" : "pre 3/5/2020 16:30",
"AnnotatedKeywordMessageSend:startTag:actualMessage:endTag:" : "joabe 9/25/2023 19:01",
"AnnotatedMessageChain:startTag:actualMessage:endTag:" : "pre 4/29/2020 17:01",
"AnnotatedOperand:startTag:actualOperand:endTag:" : "pre 3/5/2020 17:37",
"AnnotatedStatement:startTag:actualStatement:endTag:" : "jb 12/3/2020 22:36",
Expand Down
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
class initialization
clear

DefaultValue := nil
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
default

^ DefaultValue ifNil: [DefaultValue := self new]
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
as yet unclassified
addProbe: aProbe

nameToProbesDict at: aProbe className
ifPresent: [:registeredProbes | registeredProbes add: aProbe]
ifAbsent: [ | k |
k := KeyedSet keyBlock: [ :each | each variableName ].
nameToProbesDict at: aProbe className put: k]

Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
initialize-release
initialize

super initialize.
nameToProbesDict := Dictionary new.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
nameToProbesDict

^ nameToProbesDict
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
as yet unclassified
removeProbe: aProbe

nameToProbesDict at: aProbe className
ifPresent: [:registeredProbes | registeredProbes remove: aProbe]

Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
{
"class" : {
"clear" : "joabe 9/28/2023 12:59",
"default" : "joabe 9/28/2023 12:57" },
"instance" : {
"addProbe:" : "joabe 9/28/2023 13:05",
"initialize" : "joabe 9/27/2023 16:33",
"nameToProbesDict" : "joabe 9/28/2023 12:59",
"removeProbe:" : "joabe 9/27/2023 17:19" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{
"category" : "Babylonian-Core-Tracing",
"classinstvars" : [
],
"classvars" : [
"DefaultValue" ],
"commentStamp" : "",
"instvars" : [
"nameToProbesDict" ],
"name" : "BPClassNameToInstanceProbes",
"pools" : [
],
"super" : "DynamicVariable",
"type" : "normal" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
constants
annotationTag

^ 'bpInstanceProbe'
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
morphic
asMorph

| newMorph |
newMorph := BPInstanceVariableProbeMorph new
annotation: self;
yourself.
self updateTextAnchorPropertiesOf: newMorph.
^ newMorph
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
accessing
className: aString
className := aString
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
accessing
className
^ className
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
as yet unclassified
instrumentationCallFor: actualEnclosedExpressionSource

^ '(self bpTraceVariable: [{1}] forProbe: {2} inContext: thisContext)'
format: {actualEnclosedExpressionSource . self id}
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
as yet unclassified
probeTypeTag

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

"do nothing"
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
variableName: aString

variableName := aString
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
variableName

^ variableName
Original file line number Diff line number Diff line change
@@ -1,7 +1,15 @@
{
"class" : {
},
"annotationTag" : "joabe 9/25/2023 17:30" },
"instance" : {
"asMorph" : "joabe 9/21/2023 22:32",
"canBeAnnotatedTo" : "joabe 9/21/2023 21:08",
"className" : "joabe 9/27/2023 17:16",
"className:" : "joabe 9/27/2023 17:16",
"instrumentationCallFor:" : "joabe 9/25/2023 18:43",
"isInstanceVariableProbe" : "joabe 9/21/2023 21:18",
"probeTypeTag" : "joabe 9/25/2023 17:30",
"removeFromMethod:" : "joabe 9/27/2023 16:43",
"variableName" : "joabe 9/27/2023 16:52",
"variableName:" : "joabe 9/27/2023 16:52",
"wantsMetaClassIndication" : "joabe 9/21/2023 21:08" } }
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@
],
"commentStamp" : "",
"instvars" : [
],
"variableName",
"className" ],
"name" : "BPInstanceVariableProbe",
"pools" : [
],
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,12 @@
*Babylonian-Core
bpTraceVariable: aVariableName forProbe: probeId inContext: aContext

<bpRelevantMethod>
self halt.
^ aVariableName value, ' '
"^ #bpInstrumented withoutLayerDo: [
BPActiveTracer value
trace: anObject
through: [:r | r]
forProbe: probeId
inContext: aContext]"
Original file line number Diff line number Diff line change
Expand Up @@ -13,4 +13,5 @@
"bpTrace:through:forProbe:inContext:" : "jb 11/29/2020 22:12",
"bpTraceAssignmentOf:before:forProbe:inContext:" : "pre 7/6/2020 18:34",
"bpTraceExecutionResult:" : "jb 12/30/2021 21:20",
"bpTraceVariable:forProbe:inContext:" : "joabe 9/27/2023 13:36",
"isLiveSpecimenReference" : "pre 1/10/2023 16:16" } }
Empty file.
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
as yet unclassified
removeButtonClicked

super removeButtonClicked.
BPClassNameToInstanceProbes value removeProbe: self.

Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
as yet unclassified
step

| newTraces tracesChanged |
self resetHeight.

"newTraces := self getTraces asIdentitySet.
tracesChanged := newTraces ~= displayedTraces.
(allTracesCompleted not or: [tracesChanged]) ifTrue: [
allTracesCompleted := newTraces
ifEmpty: [true]
ifNotEmpty: [:ts | ts allSatisfy: [:t | t hasTraceCompleted]].
self updateFrom: (newTraces ifEmpty: [self emptyTraces]).
displayedTraces := newTraces]."

"tracesChanged ifTrue: [self refreshTextComposition]."
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
{
"class" : {
},
"instance" : {
"removeButtonClicked" : "joabe 9/27/2023 17:19",
"step" : "joabe 9/25/2023 18:34" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
{
"category" : "Babylonian-UI-Morphs",
"classinstvars" : [
],
"classvars" : [
],
"commentStamp" : "",
"instvars" : [
],
"name" : "BPInstanceVariableProbeMorph",
"pools" : [
],
"super" : "BPProbeMorph",
"type" : "normal" }
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ accessing
emphasizeScanner: scanner
"Set the emphasis for text scanning"
| emphasis |

emphasis := self anchoredMorph textEmphasis ifNil: [
self anchoredMorph visible
ifTrue: [TextEmphasis underlined]
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
"compilerClass" : "pre 11/8/2019 20:33" },
"instance" : {
"emphasisCode" : "pre 11/8/2019 13:33",
"emphasizeScanner:" : "pre 9/2/2022 15:35",
"emphasizeScanner:" : "joabe 9/21/2023 22:56",
"initialize" : "pre 7/19/2022 17:54",
"isBPDecoration" : "pre 8/17/2023 08:37",
"isOblivious" : "pre 7/9/2021 16:59",
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,19 +2,21 @@
determineIntervalOfVariableNameIn: anInterval having: aTopologicalCollectionOfAncestors

| lowestKeywordMessageSegment selectedText |

lowestKeywordMessageSegment := aTopologicalCollectionOfAncestors
detect: [:n | n ruleName = #KeywordMessageSegment]
ifNone: [^ nil].

((self contents atAll: lowestKeywordMessageSegment children first interval) ~= 'instanceVariableNames:') ifTrue: [^ nil].

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"

^ self selectedClassOrMetaClass instVarNames
detect: [:aVariable | aVariable = selectedText]
ifFound: [:matchingVariable | | start |
start := self contents findString: matchingVariable.
^ Interval from: start to: start + matchingVariable size]
^ Interval from: start to: start + matchingVariable size - 1]


Loading

0 comments on commit 8c847c6

Please sign in to comment.