Skip to content

Commit

Permalink
Merge pull request #42 from LinqLover/conveniences
Browse files Browse the repository at this point in the history
This mega PR improves several conveniences aspects of the TraceDebugger. Amongst others, this includes:

- feature: spawn trace (relates #29)
- feature: toggle border context (closes #28)
- feature: context search (closes #44)
- feature: "trace it" button in the normal debugger (closes #36)
- feature: navigation commands "jump to presence", "jump to sender", "jump to callee"
- feature: snapshot inspectors & explorers
- feature: run to selection
- improve support for code evaluation in all code panes (syntax highlighting, access to instance variables)
- working notifier window and proceed/abandon buttons, implement all remaining menu commands, clean up and rearrange menu items
- stepping improvements (coroutines, EHS)
- call tree convenience (scroll bar, display of return values, graying out dead contexts, adjust timeIndex when selecting context, support for type-to-filter)
- preference to display stack list instead of stack tree
- tracing improvements: fix tracing of coroutines and simulation (relates #14, closes #13); fix tracing of failed primitives
  • Loading branch information
LinqLover authored Mar 11, 2022
2 parents c24ff55 + f400223 commit 9f5d135
Show file tree
Hide file tree
Showing 465 changed files with 3,470 additions and 376 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*TraceDebugger-Core-proxies-converting
asTdbProxyInMemory: aMemory atTime: timeIndex

^ self
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"asTdbProxyInMemory:atTime:" : "ct 12/30/2021 23:10" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "Character" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
*TraceDebugger-Core-printing
tdbPrintSignatureOn: aStream

| class methodClass selector |
method ifNil:
[^ super printOn: aStream].

closureOrNil ifNotNil:
[aStream nextPutAll: '[] in '.
closureOrNil outerContext ifNotNil:
[:outer|
outer tdbPrintSignatureOn: aStream.
^ self]].

class := self objectClass: self receiver.
methodClass := method methodClass.
selector := method selector ifNil: [method defaultSelector].

aStream nextPutAll: class name.
methodClass ~~ class ifTrue:
[aStream nextPut: $(; nextPutAll: methodClass name; nextPut: $)].
aStream nextPutAll: '>>'; nextPutAll: selector.

(methodClass whichCategoryIncludesSelector: selector)
ifNotNil: [:category |
aStream nextPut: $ ; nextPut: ${; nextPutAll: category; nextPut: $}].
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
*TraceDebugger-Core-printing
tdbSignature

^ String streamContents: [:stream |
self tdbPrintSignatureOn: stream]
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,6 @@
"asTdbProxyInMemory:atTime:" : "ct 12/30/2021 23:14",
"tdbHasHome:" : "ct 11/30/2021 22:52",
"tdbLivingHome" : "ct 11/30/2021 22:49",
"tdbPrintSignatureOn:" : "ct 2/13/2022 01:19",
"tdbSignature" : "ct 2/3/2022 16:07",
"tdbStack" : "ct 11/19/2021 22:58" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
*TraceDebugger-UI-initialize-override
customButtonSpecs
"Answer an array of elements of the form wording, selector, help-message, that characterize the custom button row of a debugger."

| list |
list := #(('Proceed' proceed 'Close the debugger and proceed.' interruptedProcessShouldResume)
('Restart' restart 'Reset this context to its start.')
('Into' stepInto 'step Into message sends' interruptedProcessIsActive)
('Over' stepOver 'step Over message sends' interruptedProcessIsActive)
('Through' stepThrough 'step into a block' interruptedProcessIsActive)
('Full Stack' showFullStack 'show full stack')
('Where' showWhere 'select current pc range')
('Trace It' trace 'switch to a TraceDebugger')).
(Preferences restartAlsoProceeds and: [self interruptedProcessShouldResume]) ifTrue:
[list := list collect: [:each |
each second == #restart
ifTrue: [each copy
at: 1 put: 'Proceed Here';
at: 3 put: 'Proceed from the beginning of this context.';
yourself]
ifFalse: [each second == #proceed
ifTrue: [each copy
at: 1 put: 'Proceed Top';
at: 3 put: 'Proceed from the current top context.';
yourself]
ifFalse: [each]]]].
^ list
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
*TraceDebugger-UI
trace

| currentBounds process context oldInspectors traceDebugger window postBuild |
self okToChange ifFalse: [^ self changed: #flash].

"Save current state"
currentBounds := ToolBuilder default class getBoundsForWindow: self containingWindow.

"Close first because MVC fiddles around with processes."
process := self interruptedProcess.
interruptedProcess := nil. "Before delete, so release doesn't terminate it"
context := self selectedContext.
oldInspectors := #(receiverInspector contextVariablesInspector)
collect: [:path | path -> (path value: self)]
as: Dictionary.
self close.

traceDebugger := (TraceDebugger newOn: process context: process suspendedContext)
messageText: message;
yourself.
(self respondsTo: #errorWasInUIProcess) ifTrue:
[traceDebugger errorWasInUIProcess: self errorWasInUIProcess].
postBuild := nil.
"Copy old state to new window"
traceDebugger selectContext: context.
oldInspectors keysAndValuesDo: [:path :oldInspector | | newInspector |
newInspector := path value: traceDebugger.
oldInspector customFields do: [:field |
newInspector addCustomField: field].
newInspector selectFieldNamed: oldInspector selectedFieldName.
oldInspector contentsTyped ifNotNil: [:contents | | previousBuild |
newInspector contentsTyped: contents.
"Updating strings is only possible after toolbuilding"
previousBuild := postBuild.
postBuild := [previousBuild value.
newInspector changed: #editString with: contents]]].

"Open"
window := traceDebugger openFull: true label: self labelString.
"---- In MVC, the lines after this will not be executed ---"
ToolBuilder default class setBoundsForWindow: window to: currentBounds.

postBuild value.
^ window
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
{
"class" : {
},
"instance" : {
"customButtonSpecs" : "ct 2/8/2022 20:04",
"trace" : "ct 3/10/2022 14:57" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "Debugger" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*TraceDebugger-UI-converting
asTdbProxyHolderFor: originalTdbProxyHolder

^ originalTdbProxyHolder tdbInspectorFor: self
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"asTdbProxyHolderFor:" : "ct 3/10/2022 22:39" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "Inspector" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
*TraceDebugger-UI-converting
tdbReplaceModelDeeply: aModel
"Replace all occurences of the current receiver model in the receiver and all its ancestors with aModel."

| oldModel |
oldModel := self model.
self allMorphsDo: [:morph |
morph model == oldModel
ifTrue: [morph model: aModel]].
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"tdbReplaceModelDeeply:" : "ct 3/10/2022 22:44" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "MorphicModel" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*TraceDebugger-UI-converting
asTdbProxyHolderFor: originalTdbProxyHolder

^ self
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*TraceDebugger-UI-testing
isTdbProxyHolder

^ false
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
*TraceDebugger-Core
tdbHalt
"This is the typical message to use for inserting breakpoints during
debugging. It behaves like halt:, but does not call on halt: in order to
avoid putting this message on the stack. Halt is especially useful when
the breakpoint message is an arbitrary one."

^ TraceDebugger
openOn: Processor activeProcess
context: thisContext sender
label: thisContext sender selector
contents: nil
fullView: false
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
*TraceDebugger-Core
tdbNotify: aStringOrText
"Create and schedule a Notifier with the argument as the message in
order to request confirmation before a process can proceed."

^ TraceDebugger
openOn: Processor activeProcess
context: thisContext sender
label: thisContext sender selector
contents: aStringOrText
fullView: false
Original file line number Diff line number Diff line change
Expand Up @@ -2,5 +2,9 @@
"class" : {
},
"instance" : {
"asTdbProxyHolderFor:" : "ct 3/10/2022 22:39",
"isTdbProxyHolder" : "ct 3/10/2022 22:39",
"tdbHalt" : "ct 1/26/2022 20:14",
"tdbIdentical:" : "ct 12/2/2021 01:21",
"tdbNotify:" : "ct 1/26/2022 20:28",
"tdbproxyYourself" : "ct 11/20/2021 20:20" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
*TraceDebugger-UI-instance creation-pseudo-override
on: anObject

self flag: #moveUpstream.

^ self explore: anObject
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
*TraceDebugger-UI-converting
asTdbProxyHolderFor: originalTdbProxyHolder

^ originalTdbProxyHolder tdbExplorerFor: self
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
"on:" : "ct 3/10/2022 22:45" },
"instance" : {
"asTdbProxyHolderFor:" : "ct 3/10/2022 22:39" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "ObjectExplorer" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
*TraceDebugger-UI-event handling-override
dropSourceCode: anObject event: evt

| tool window |
self flag: #(override moveUpstream). "Preview for genericDropSourceCode.cs"

(anObject isMethodReference and: [anObject isValid])
ifTrue: [^ self dropSourceCode: anObject compiledMethod event: evt].

anObject isString
ifTrue: [^ anObject edit].

tool := (anObject isBehavior or: [anObject isCompiledMethod])
ifTrue: [
anObject isBehavior
ifTrue: [Browser new
setClass: anObject]
ifFalse: [CodeHolder new
setClass: anObject methodClass
selector: anObject selector]]
ifFalse: [anObject browse].

window := tool containingWindow ifNil: [ToolBuilder open: tool].
window center: evt position.
window bounds: (window bounds translatedToBeWithin: self bounds).
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"dropSourceCode:event:" : "ct 2/3/2022 14:17" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "PasteUpMorph" }
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
*TraceDebugger-UI-copying
tdbWithoutPrefix: prefix

(self beginsWith: prefix)
ifFalse: [^ self].
^ self allButFirst: prefix size
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
{
"class" : {
},
"instance" : {
"tdbWithoutPrefix:" : "ct 1/26/2022 20:21" } }
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
{
"name" : "SequenceableCollection" }
Original file line number Diff line number Diff line change
@@ -1,9 +1,5 @@
accessing
closure

^ (memory
object: object
atTime: timeIndex
instVarAt: 5 "closureOrNil"
ifAbsent: [object closure])
tdbInMemory: memory atTime: timeIndex
^ object closure
tdbInMemory: memory atTime: timeIndex
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
accessing
home

^ object home
tdbInMemory: memory atTime: timeIndex
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
accessing
methodClass

^ self method methodClass ifNil: [object objectClass: self receiver]
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
accessing
receiver

^ (memory
object: object
atTime: timeIndex
instVarAt: 6 "receiver"
ifAbsent: [object receiver])
tdbInMemory: memory atTime: timeIndex
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
printing
tdbPrintSignatureOn: aStream

| method class methodClass selector |
method := self method ifNil:
[^ super printOn: aStream].

self closure ifNotNil: [:closure |
aStream nextPutAll: '[] in '.
closure outerContext ifNotNil:
[:outer|
outer tdbPrintSignatureOn: aStream.
^ self]].

class := object objectClass: self receiver tdbproxyYourself.
methodClass := method methodClass.
selector := method selector ifNil: [method defaultSelector].

aStream nextPutAll: class name.
methodClass ~~ class ifTrue:
[aStream nextPut: $(; nextPutAll: methodClass name; nextPut: $)].
aStream nextPutAll: '>>'; nextPutAll: selector.

(methodClass whichCategoryIncludesSelector: selector)
ifNotNil: [:category |
aStream nextPut: $ ; nextPut: ${; nextPutAll: category; nextPut: $}].
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
printing
tdbSignature

^ String streamContents: [:stream |
self tdbPrintSignatureOn: stream]
Original file line number Diff line number Diff line change
Expand Up @@ -2,13 +2,18 @@
"class" : {
},
"instance" : {
"closure" : "ct 1/23/2022 20:41",
"closure" : "ct 2/3/2022 18:56",
"debuggerMap" : "ct 12/30/2021 23:23",
"home" : "ct 2/3/2022 18:56",
"isDead" : "ct 1/23/2022 20:26",
"method" : "ct 12/30/2021 23:23",
"methodClass" : "ct 2/4/2022 17:44",
"pc" : "ct 1/23/2022 20:26",
"receiver" : "ct 2/3/2022 18:56",
"selector" : "ct 12/30/2021 23:18",
"startpc" : "ct 1/23/2022 20:24",
"tdbHasHome:" : "ct 1/23/2022 20:30",
"tdbIdentical:" : "ct 12/31/2021 02:33",
"tdbPrintSignatureOn:" : "ct 2/13/2022 01:19",
"tdbSignature" : "ct 2/3/2022 16:08",
"tempNames" : "ct 12/31/2021 00:51" } }
Loading

0 comments on commit 9f5d135

Please sign in to comment.