#UI_ENHANCEMENT by cg
authorClaus Gittinger <cg@exept.de>
Sat, 28 Jul 2018 11:54:43 +0200
changeset 18300 5bfb159a26fa
parent 18299 bb1a38c70b85
child 18301 4a1ce140ef70
#UI_ENHANCEMENT by cg class: DebugView class definition added: #initializeInfoPanelIn: #initializeViews comment/format in: #helpTextFor: changed: #helpTextFor:at: #initialize #showValue: #withNodeValueAtInterval:do:
DebugView.st
--- a/DebugView.st	Sat Jul 28 11:07:25 2018 +0200
+++ b/DebugView.st	Sat Jul 28 11:54:43 2018 +0200
@@ -37,7 +37,7 @@
 		classToDefineIn gotoApplicationActionMethodButton
 		isStoppedInApplicationAction isStoppedAtStatementBreakpoint
 		verboseBacktraceHolder foundRaisingMethod gotoRaisingMethodButton
-		stepInButton'
+		stepInButton infoLabelHolder'
 	classVariableNames:'CachedDebugger CachedExclusive OpenDebuggers MoreDebuggingDetail
 		DebuggingDebugger DebuggingDebugger2 DebuggingContextWalk
 		DefaultDebuggerBackgroundColor InitialNChainShown IgnoredHalts
@@ -2891,15 +2891,12 @@
         ((localPoint x between:0 and:codeView width)
         and:[localPoint y between:0 and:codeView height])
         ifTrue:[
-            ^ self helpTextFor:codeView at:localPoint
+            s := self helpTextFor:codeView at:localPoint.
+            ^ s
         ].
         ^ nil
     ].
 
-"/    aComponent == abortButton ifTrue:[
-"/        "/ s := 'Abort (unwind to eventLoop)'
-"/        s := 'HELP_ABORT'
-"/    ].
     aComponent == terminateButton ifTrue:[
         Processor activeProcess isGUIProcess ifTrue:[
             s := 'HELP_TERMINATE_GUI'
@@ -2920,33 +2917,6 @@
             s := 'HELP_CONTINUE'
         ]
     ].
-"/    aComponent == stepButton ifTrue:[
-"/        "/ s := 'Step to next send in selected context (don''t enter into called methods)'
-"/        s := 'HELP_STEP'
-"/    ].
-"/    aComponent == stepInButton ifTrue:[
-"/        "/ s := 'Step into next send in selected context (enter into called methods)'
-"/        s := 'HELP_STEPIN'
-"/    ].
-"/    aComponent == nextButton ifTrue:[
-"/        "/ s := 'Step to next line in selected context (don''t enter into called methods)'
-"/        s := 'HELP_NEXT'
-"/    ].
-"/    aComponent == nextOverButton ifTrue:[
-"/        "/ s := 'Step over to cursor-line'
-"/        s := 'HELP_NEXTOVER'
-"/    ].
-"/    aComponent == nextOutButton ifTrue:[
-"/        "/ s := 'Step out to caller'
-"/        s := 'HELP_NEXTOUT'
-"/    ].
-"/    aComponent == stepButton ifTrue:[
-"/        s := 'HELP_STEP'
-"/    ].
-"/    aComponent == sendButton ifTrue:[
-"/        "/ s := 'Send next message (enter into called methods)'
-"/        s := 'HELP_SEND'
-"/    ].
     aComponent == returnButton ifTrue:[
         returnButton enabled ifTrue:[
             "/ s := 'Return from the selected method'
@@ -2974,41 +2944,16 @@
             s := 'HELP_RESEND_DISABLED'
         ].
     ].
-"/    aComponent == contextView ifTrue:[
-"/        s := 'HELP_WALKBACK'
-"/    ].
-"/    aComponent == codeView ifTrue:[
-"/        s := 'HELP_CODEVIEW'
-"/    ].
-"/    aComponent == monitorToggle ifTrue:[
-"/        "/ s := 'Toggle monitoring'
-"/        s := 'HELP_MONITOR'
-"/    ].
     aComponent == updateButton ifTrue:[
         "/ s := 'Update'
         s := 'HELP_UPDATE'
     ].
-"/    aComponent == gotoDialogOpenerButton ifTrue:[
-"/        s := 'HELP_GOTO_DIALOG_OPENER'
-"/    ].
-"/    aComponent == gotoApplicationActionMethodButton ifTrue:[
-"/        s := 'HELP_GOTO_APPLICATION_ACTION'
-"/    ].
-"/    aComponent == stopButton ifTrue:[
-"/        s := 'HELP_STOP'
-"/    ].
     aComponent == defineButton ifTrue:[
         s := 'Define the missing method (as halting) and proceed into it.\A debugger will reopen there, so you can add the code then'
     ].
     aComponent == reportButton ifTrue:[
         s := 'Send a defect report via eMail'
     ].
-"/    (aComponent isComponentOf:receiverInspector) ifTrue:[
-"/        s := 'HELP_REC_INSP'
-"/    ].
-"/    (aComponent isComponentOf:contextInspector) ifTrue:[
-"/        s := 'HELP_CON_INSP'
-"/    ].
 
     s := s ? (aComponent helpKey).
     s notNil ifTrue:[
@@ -3018,7 +2963,7 @@
 
     "Modified: / 29-08-1995 / 23:38:54 / claus"
     "Modified: / 04-03-1997 / 01:54:03 / cg"
-    "Modified: / 13-06-2018 / 11:14:49 / Claus Gittinger"
+    "Modified: / 28-07-2018 / 11:52:46 / Claus Gittinger"
 !
 
 helpTextFor:aComponent at:aPointOrNil
@@ -3026,7 +2971,7 @@
 
     aComponent == codeView ifFalse:[^ nil].
     aPointOrNil isNil ifTrue:[^ nil].
-    self sensor motionEventPending ifTrue:[^ nil].
+    "/ self sensor motionEventPending ifTrue:[^ nil].
 
     vline := codeView visibleLineOfY:aPointOrNil y.
     col := codeView colOfX:aPointOrNil x inVisibleLine:vline.
@@ -3078,10 +3023,16 @@
                 s := description , ': ', valueString, valueClassOrSizeString
             ].
         ].
-    "/ Transcript showCR:s.
+
+    "/ if there is an infoLabelHolder, show it there    
+    infoLabelHolder notNil ifTrue:[
+        infoLabelHolder value:s.
+        ^ ''
+    ].
     ^ s
 
     "Modified: / 27-04-2010 / 17:51:53 / cg"
+    "Modified: / 28-07-2018 / 11:54:13 / Claus Gittinger"
 ! !
 
 !DebugView methodsFor:'initialization & release'!
@@ -3158,9 +3109,6 @@
 !
 
 initialize
-    |menu menuPanel mH panel bpanel bH bpanel1 bH1 bpanel2 bH2 codePanel
-     newLayout v exceptionAndTogglePanel codeToggleLabels|
-
     super initialize.
 
     self initializeFlags.
@@ -3173,108 +3121,7 @@
     stepHow := nil.
     canContinue := false.
 
-    mH := 0.
-
-    menuPanel := MenuPanel in:self.
-    menuPanel receiver:self.
-    menuPanel verticalLayout:false.
-    menu := self class menuSpec decodeAsLiteralArray.
-    menu findGuiResourcesIn:self.
-    menuPanel menu:menu.
-
-    mH := menuPanel preferredHeight.
-    menuPanel origin:(0.0 @ 0.0) corner:(1.0 @ (mH)).
-
-    newLayout := UserPreferences current useNewLayoutInDebugger.
-    newLayout ifFalse:[
-        bpanel := HorizontalPanelView in:self.
-
-        self initializeButtonsIn:bpanel.
-
-        bH := bpanel preferredHeight + 5.
-        bpanel origin:(0.0 @ mH)
-               extent:(1.0 @ bH).
-        panel := VariableVerticalPanel
-                            origin:(0.0 @ (mH + bH))
-                            corner:(1.0 @ 1.0)
-                            in:self.
-
-        v := self initializeContextListViewIn:panel.
-        v origin:(0.0 @ 0.0) corner:(1.0 @ 0.25).
-
-        codePanel := View in:panel.
-        v := self initializeCodeViewIn:codePanel.
-        v origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
-        codePanel origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).
-
-        v := self initializeInspectorViewsIn:panel.
-        v origin:(0.0 @ 0.75) corner:(1.0 @ 1.0).
-
-    ] ifTrue:[
-        bpanel1 := HorizontalPanelView in:self.
-        self initializeButtons1In:bpanel1.
-
-        contextInfoLabel := Label label:''.
-        contextInfoLabel adjust:#left.
-        bpanel1 add:contextInfoLabel.
-
-        bH1 := bpanel1 preferredHeight + 5.
-        bpanel1 origin:(0.0 @ mH)
-                extent:(1.0 @ bH1).
-        panel := VariableVerticalPanel
-                            origin:(0.0 @ (mH + bH1))
-                            corner:(1.0 @ 1.0)
-                                in:self.
-        "/ panel showHandle:true.
-        "/ panel handlePosition:#left.
-
-        v := self initializeContextListViewIn:panel.
-        v origin:(0.0 @ 0.0) corner:(1.0 @ 0.25).
-
-        codePanel := View in:panel.
-        bpanel2 := HorizontalPanelView in:codePanel.
-        self initializeButtons2In:bpanel2.
-
-        bH2 := bpanel2 preferredHeight + 5.
-        bpanel2 origin:(0.0 @ 0.0)
-                extent:(1.0 @ bH2).
-
-        exceptionInfoLabel := Label label:''.
-        exceptionInfoLabel adjust:#left.
-
-        exceptionAndTogglePanel := HorizontalPanelView in:codePanel.
-        exceptionAndTogglePanel horizontalLayout:#left.
-        exceptionAndTogglePanel
-            geometryLayout:
-                ((LayoutFrame
-                    origin:(0.0 @ 0.0)
-                    corner:(1.0 @ 0.0))
-                        topOffset:bH2;
-                        bottomOffset:(bH2 + exceptionInfoLabel preferredHeight + 6);
-                        rightOffset:-2).
-
-        methodCodeToggleSelectionHolder := 1 asValue.
-        methodCodeToggleSelectionHolder onChangeSend:#methodCodeToggleChanged to:self.
-        codeToggleLabels := resources array:{
-                    'Showing Original Code (being executed, but obsolete)' asText backgroundColorizeAllWith:Color red lightened .
-                    'Showing Current Code'                                 asText backgroundColorizeAllWith:Color green lightened .
-                  }.
-        methodCodeToggle := PopUpList label:codeToggleLabels first in:exceptionAndTogglePanel.
-        methodCodeToggle list:codeToggleLabels.
-        methodCodeToggle useIndex:true.
-        methodCodeToggle model:methodCodeToggleSelectionHolder.
-        methodCodeToggle beInvisible.
-
-        exceptionAndTogglePanel add:exceptionInfoLabel.
-
-        v := self initializeCodeViewIn:codePanel.
-        v origin:(0.0 @ (bH2+exceptionInfoLabel preferredHeight+6)) corner:(1.0 @ 1.0).
-        codePanel origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).
-
-        v := self initializeInspectorViewsIn:panel.
-        v origin:(0.0 @ 0.75) corner:(1.0 @ 1.0).
-    ].
-
+    self initializeViews.
     DefaultDebuggerBackgroundColor notNil ifTrue:[
         self allViewBackground:DefaultDebuggerBackgroundColor.
     ].
@@ -3290,6 +3137,7 @@
     "
 
     "Modified: / 27-07-2012 / 14:46:07 / cg"
+    "Modified: / 28-07-2018 / 11:15:15 / Claus Gittinger"
 !
 
 initializeAbortButtonIn:bpanel
@@ -3680,6 +3528,33 @@
     "Created: / 30-11-2017 / 12:09:54 / cg"
 !
 
+initializeInfoPanelIn:aView
+    |infoPanel infoLabel|
+    
+    infoPanel := HorizontalPanelView in:aView.
+    infoPanel geometryLayout:(LayoutFrame
+                            leftFraction:0.0 offset:0 
+                            rightFraction:1.0 offset:0 
+                            topFraction:1.0 offset:-25
+                            bottomFraction:1.0 offset:0).
+    infoLabel := Label in:infoPanel.
+    infoLabel geometryLayout:(LayoutFrame
+                            leftFraction:0.0 offset:0 
+                            rightFraction:1.0 offset:0 
+                            topFraction:0.0 offset:0
+                            bottomFraction:1.0 offset:0).
+
+    infoLabel adjust:#left.
+    infoLabel labelChannel:(infoLabelHolder := '' asValue).
+
+    "
+     Debugger newDebugger.
+     self halt.
+    "
+
+    "Created: / 28-07-2018 / 11:23:41 / Claus Gittinger"
+!
+
 initializeInspectorViewsIn:panel
     |hpanel|
 
@@ -3831,6 +3706,127 @@
     "Created: / 17.11.2001 / 21:02:20 / cg"
 !
 
+initializeViews
+    |menu menuPanel mH panel bpanel bH bpanel1 bH1 bpanel2 bH2 codePanel
+     newLayout v exceptionAndTogglePanel codeToggleLabels|
+
+    mH := 0.
+
+    menuPanel := MenuPanel in:self.
+    menuPanel receiver:self.
+    menuPanel verticalLayout:false.
+    menu := self class menuSpec decodeAsLiteralArray.
+    menu findGuiResourcesIn:self.
+    menuPanel menu:menu.
+
+    mH := menuPanel preferredHeight.
+    menuPanel origin:(0.0 @ 0.0) corner:(1.0 @ (mH)).
+
+    newLayout := UserPreferences current useNewLayoutInDebugger.
+    newLayout ifFalse:[
+        bpanel := HorizontalPanelView in:self.
+        self initializeButtonsIn:bpanel.
+        bH := bpanel preferredHeight + 5.
+        bpanel origin:(0.0 @ mH) extent:(1.0 @ bH).
+               
+        self initializeInfoPanelIn:self.
+        
+        panel := VariableVerticalPanel in:self.
+        "/ panel origin:(0.0 @ (mH + bH)) corner:(1.0 @ 1.0).
+        panel geometryLayout:(LayoutFrame
+                                leftFraction:0.0 offset:0 
+                                rightFraction:1.0 offset:0 
+                                topFraction:0 offset:(mH + bH)
+                                bottomFraction:1.0 offset:-25).
+
+        v := self initializeContextListViewIn:panel.
+        v origin:(0.0 @ 0.0) corner:(1.0 @ 0.25).
+
+        codePanel := View in:panel.
+        v := self initializeCodeViewIn:codePanel.
+        v origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
+        codePanel origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).
+
+        v := self initializeInspectorViewsIn:panel.
+        v origin:(0.0 @ 0.75) corner:(1.0 @ 1.0).
+
+    ] ifTrue:[
+        self initializeInfoPanelIn:self.
+        
+        bpanel1 := HorizontalPanelView in:self.
+        self initializeButtons1In:bpanel1.
+
+        contextInfoLabel := Label label:''.
+        contextInfoLabel adjust:#left.
+        bpanel1 add:contextInfoLabel.
+
+        bH1 := bpanel1 preferredHeight + 5.
+        bpanel1 origin:(0.0 @ mH) extent:(1.0 @ bH1).
+
+        panel := VariableVerticalPanel in:self.
+        "/ panel origin:(0.0 @ (mH + bH1)) corner:(1.0 @ 1.0).
+        panel geometryLayout:(LayoutFrame
+                                leftFraction:0.0 offset:0 
+                                rightFraction:1.0 offset:0 
+                                topFraction:0 offset:(mH + bH1)
+                                bottomFraction:1.0 offset:-25).
+                                
+        "/ panel showHandle:true.
+        "/ panel handlePosition:#left.
+
+        v := self initializeContextListViewIn:panel.
+        v origin:(0.0 @ 0.0) corner:(1.0 @ 0.25).
+
+        codePanel := View in:panel.
+        bpanel2 := HorizontalPanelView in:codePanel.
+        self initializeButtons2In:bpanel2.
+
+        bH2 := bpanel2 preferredHeight + 5.
+        bpanel2 origin:(0.0 @ 0.0) extent:(1.0 @ bH2).
+
+        exceptionInfoLabel := Label label:''.
+        exceptionInfoLabel adjust:#left.
+
+        exceptionAndTogglePanel := HorizontalPanelView in:codePanel.
+        exceptionAndTogglePanel horizontalLayout:#left.
+        exceptionAndTogglePanel
+            geometryLayout:
+                ((LayoutFrame
+                    origin:(0.0 @ 0.0)
+                    corner:(1.0 @ 0.0))
+                        topOffset:bH2;
+                        bottomOffset:(bH2 + exceptionInfoLabel preferredHeight + 6);
+                        rightOffset:-2).
+
+        methodCodeToggleSelectionHolder := 1 asValue.
+        methodCodeToggleSelectionHolder onChangeSend:#methodCodeToggleChanged to:self.
+        codeToggleLabels := resources array:{
+                    'Showing Original Code (being executed, but obsolete)' asText backgroundColorizeAllWith:Color red lightened .
+                    'Showing Current Code'                                 asText backgroundColorizeAllWith:Color green lightened .
+                  }.
+        methodCodeToggle := PopUpList label:codeToggleLabels first in:exceptionAndTogglePanel.
+        methodCodeToggle list:codeToggleLabels.
+        methodCodeToggle useIndex:true.
+        methodCodeToggle model:methodCodeToggleSelectionHolder.
+        methodCodeToggle beInvisible.
+
+        exceptionAndTogglePanel add:exceptionInfoLabel.
+
+        v := self initializeCodeViewIn:codePanel.
+        v origin:(0.0 @ (bH2+exceptionInfoLabel preferredHeight+6)) corner:(1.0 @ 1.0).
+        codePanel origin:(0.0 @ 0.25) corner:(1.0 @ 0.75).
+
+        v := self initializeInspectorViewsIn:panel.
+        v origin:(0.0 @ 0.75) corner:(1.0 @ 1.0).
+    ].
+
+    "
+     Debugger newDebugger
+    "
+
+    "Created: / 28-07-2018 / 11:14:52 / Claus Gittinger"
+!
+
 postRealize
     super postRealize.
 
@@ -7153,8 +7149,9 @@
 !
 
 showValue:aValue
-    "/ TODO: show value in info field
-    "/ Transcript showCR:aValue printString
+    infoLabelHolder value:aValue printString
+
+    "Modified: / 28-07-2018 / 11:25:57 / Claus Gittinger"
 !
 
 stepping
@@ -7254,7 +7251,9 @@
 !
 
 withNodeValueAtInterval:interval do:aBlock
-    "helper for tooltops and explan-selection"
+    "helper for tooltops and explain-selection;
+     evaluate aBlock with description of what it is and its value
+     (if known)"
 
     |node definingNode nm nmBold nameSymbol
      varIdx parentNode receiver con receiversNonMetaClass|
@@ -7296,7 +7295,6 @@
     definingNode := node whoDefines:nm.
     definingNode isNil ifTrue:[
         (receiver class allInstVarNames includes:nm) ifTrue:[
-"/aBlock value:'xIII' value:'instVar'.
             receiver class isMetaclass ifTrue:[
                 aBlock value:(receiver instVarNamed:nm) value:'classInstVar ',nmBold.
             ] ifFalse:[
@@ -7328,7 +7326,8 @@
         nameSymbol notNil ifTrue:[
             (Smalltalk includesKey:nameSymbol) ifTrue:[
                 (Smalltalk at:nameSymbol) isClass ifTrue:[
-                    aBlock value:'class: ',nmBold value:nil.
+                    aBlock value:(Smalltalk at:nameSymbol) value:''.
+                    "/ aBlock value:''(Smalltalk at:nameSymbol) value:'class ',nmBold.
                 ] ifFalse:[
                     aBlock value:(Smalltalk at:nameSymbol) value:'global ',nmBold.
                 ].
@@ -7434,6 +7433,7 @@
     aBlock value:nmBold , ' is not in scope of selected context' value:nil.
 
     "Modified: / 18-01-2011 / 17:57:34 / cg"
+    "Modified: / 28-07-2018 / 11:46:46 / Claus Gittinger"
 ! !
 
 !DebugView methodsFor:'private queries'!