NewInspectorPanelView.st
changeset 2621 285fa261cbcb
parent 2299 fff41ffaaf26
--- a/NewInspectorPanelView.st	Wed Oct 14 08:13:10 2009 +0200
+++ b/NewInspectorPanelView.st	Wed Oct 14 13:43:27 2009 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -11,7 +11,7 @@
 "
 "{ Package: 'stx:libtool2' }"
 
-"{ NameSpace: NewInspector }"
+"{ NameSpace: Tools }"
 
 SimpleView subclass:#NewInspectorPanelView
 	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
@@ -26,7 +26,7 @@
 copyright
 "
  COPYRIGHT (c) 1997 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -44,20 +44,20 @@
     example 1
     =========
 
-                                                                        [exBegin]
+									[exBegin]
     |top slv|
 
     top := StandardSystemView new extent:600@400.
-    slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
+    slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
     slv inspect:top.
     slv action:[:el|Transcript showCR:el].
     top open.
-                                                                        [exEnd]
+									[exEnd]
 
 
     example 2
     =========
-                                                                        [exBegin]
+									[exBegin]
     |top slv edt a vvp|
 
     a := Array new:5.
@@ -66,7 +66,7 @@
     top := StandardSystemView new extent:600@400.
     vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
 
-    slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
+    slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
     edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
     edt acceptAction:[:theText|slv accept:theText notifying:edt].
     edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
@@ -75,7 +75,7 @@
     slv inspect:a.
 
     top open.
-                                                                        [exEnd]
+									[exEnd]
 "
 ! !
 
@@ -103,25 +103,25 @@
     min := self class minDepth.
 
     aDepth > min ifTrue:[
-        sz := aDepth min:maxDepth.
+	sz := aDepth min:maxDepth.
 
-        sz < listViews size ifTrue:[
-            sz := listViews size
-        ]
+	sz < listViews size ifTrue:[
+	    sz := listViews size
+	]
     ] ifFalse:[
-        sz := min
+	sz := min
     ].
 
     listViews size == sz ifTrue:[
-        sz == aDepth ifFalse:[self moveContentsLeft:1].
+	sz == aDepth ifFalse:[self moveContentsLeft:1].
     ] ifFalse:[
-        [self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
-        self computeExtentOfFrames.
+	[self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
+	self computeExtentOfFrames.
 
-        (self topView shown) ifTrue:[
-            hzpView sizeChanged:nil.
-            hzpView realizeAllSubViews.
-        ]
+	(self topView shown) ifTrue:[
+	    hzpView sizeChanged:nil.
+	    hzpView realizeAllSubViews.
+	]
     ]
 !
 
@@ -133,13 +133,13 @@
     "change max depth for instance
     "
     aNumber > listViews size ifTrue:[
-        aNumber >= (self class minDepth) ifTrue:[
-            maxDepth := aNumber.
+	aNumber >= (self class minDepth) ifTrue:[
+	    maxDepth := aNumber.
 
-            maxDepth < listViews size ifTrue:[
-                self depth:maxDepth
-            ]
-        ]
+	    maxDepth < listViews size ifTrue:[
+		self depth:maxDepth
+	    ]
+	]
     ]
 ! !
 
@@ -237,17 +237,17 @@
     sivar := view selectedInstanceVar.
 
     start > listViews size ifTrue:[
-        start >= maxDepth ifTrue:[
-            self moveContentsLeft:1.
-          ^ actionBlock value:sivar.
-        ].
+	start >= maxDepth ifTrue:[
+	    self moveContentsLeft:1.
+	  ^ actionBlock value:sivar.
+	].
     ].
 
     (view selectedInstanceType) == #directory ifTrue:[
-        (listViews at:start) setSelection:nil.
-        (listViews at:start) inspect:sivar.
-        
-        start := start + 1.
+	(listViews at:start) setSelection:nil.
+	(listViews at:start) inspect:sivar.
+
+	start := start + 1.
     ].
 
     listViews from:start do:[:v|v inspect:nil].
@@ -309,9 +309,9 @@
     |cls|
 
     anIndex <= labelViews size ifTrue:[
-        (cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
-            anAction value:cls
-        ]
+	(cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
+	    anAction value:cls
+	]
     ]
 
 !
@@ -325,11 +325,11 @@
     sqNr := labelViews findFirst:[:v| v == view].
 
     sqNr ~~ 0 ifTrue:[
-        view := labelViews at:sqNr.
+	view := labelViews at:sqNr.
 
-        view label notEmpty ifTrue:[
-            ^ self labelMenu:sqNr
-        ]
+	view label notEmpty ifTrue:[
+	    ^ self labelMenu:sqNr
+	]
     ].
     ^ nil
 !
@@ -340,16 +340,16 @@
     |menu|
 
     menu := PopUpMenu labels:#(
-                              'browse'
-                              'browse class hierarchy'
-                              'browse full class protocol'
-                              )
-                   selectors:#( 
-                              browse:
-                              browseClassHierarchy:
-                              browseFullClassProtocol:
-                              )
-                    receiver:self.
+			      'browse'
+			      'browse class hierarchy'
+			      'browse full class protocol'
+			      )
+		   selectors:#(
+			      browse:
+			      browseClassHierarchy:
+			      browseFullClassProtocol:
+			      )
+		    receiver:self.
 
    menu args:(Array new:(menu labels size) withAll:anIndex).
  ^ menu
@@ -366,7 +366,7 @@
     selectors := self messageMenu:anInstance.
 
     selectors notNil ifTrue:[
-        self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
+	self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
     ].
 
 !
@@ -385,7 +385,7 @@
     selectors := self messageMenu:anInstance.
 
     selectors notNil ifTrue:[
-        self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
+	self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
     ]
 !
 
@@ -434,16 +434,16 @@
     btp bottomInset:viewSpacing.
 
     slv := ScrollableView for:SelectionInListView
-                miniScrollerV:true
-                       origin:(0.0 @ 0.0)
-                       corner:(0.5 @ 1.0)
-                           in:hzp.
+		miniScrollerV:true
+		       origin:(0.0 @ 0.0)
+		       corner:(0.5 @ 1.0)
+			   in:hzp.
 
     acv := ScrollableView for:SelectionInListView
-                miniScrollerV:true
-                       origin:(0.5 @ 0.0)
-                       corner:(1.0 @ 1.0)
-                           in:hzp.
+		miniScrollerV:true
+		       origin:(0.5 @ 0.0)
+		       corner:(1.0 @ 1.0)
+			   in:hzp.
 
     slv := slv scrolledView.
     acv := acv scrolledView.
@@ -452,19 +452,19 @@
     acl := OrderedCollection new.
 
     (MessageTracer wrappedSelectorsOf:anInstance) do:[:el|
-        el notNil ifTrue:[
-            acl add:el.
-            sll remove:el ifAbsent:nil
-        ]
+	el notNil ifTrue:[
+	    acl add:el.
+	    sll remove:el ifAbsent:nil
+	]
     ].
-        
+
     slv list:(sll copy).
     acv list:(acl copy).
 
     dblClcAct := [:from :to|
-        to add:(from selectionValue).
-        from removeIndex:(from selection).
-        from redraw.
+	to add:(from selectionValue).
+	from removeIndex:(from selection).
+	from redraw.
     ].
 
     slv doubleClickAction:[:index| dblClcAct value:slv value:acv].
@@ -473,18 +473,18 @@
     top openModal.
 
     accepted ifFalse:[
-        ^ nil
+	^ nil
     ].
     lst := acv list.
 
 "undo existing traps            HACK: removes traps and traces"
 
     acl notEmpty ifTrue:[
-        MessageTracer untrace:anInstance
+	MessageTracer untrace:anInstance
     ].
 
     lst notEmpty ifTrue:[^ lst]
-                ifFalse:[^ nil]
+		ifFalse:[^ nil]
 !
 
 viewMenu
@@ -496,7 +496,7 @@
     sqNr := listViews findFirst:[:v| v == view].
 
     sqNr notNil ifTrue:[^ self viewMenu:sqNr]
-               ifFalse:[^ nil]
+	       ifFalse:[^ nil]
 !
 
 viewMenu:anIndex
@@ -509,52 +509,52 @@
     inst := view selectedInstanceVar.
 
     menu := PopUpMenu labels:#( 'update' )
-                   selectors:#( #update  )
-                    receiver:self.
+		   selectors:#( #update  )
+		    receiver:self.
 
     menu actionAt:#update put:[
-        view update.
+	view update.
 
-        listViews from:(anIndex + 1) do:[:v|
-            (view selectedInstanceType) ~~ #directory ifTrue:[
-                v inspect:nil
-            ] ifFalse:[
-                v inspect:(view selectedInstanceVar).
-                view := v.
-            ]
-        ].
-        self update
+	listViews from:(anIndex + 1) do:[:v|
+	    (view selectedInstanceType) ~~ #directory ifTrue:[
+		v inspect:nil
+	    ] ifFalse:[
+		v inspect:(view selectedInstanceVar).
+		view := v.
+	    ]
+	].
+	self update
     ].
 
     (NewInspectorList isTraceable:inst) ifFalse:[
-        ^ menu
+	^ menu
     ].
 
     menu  addLabels:#(
-                      '-'
-                      'trace'
-                      'trap'
-                      'untrace / untrap'
-                     )
-          selectors:#(
-                      nil
-                      trace
-                      trap
-                      untrace
-                     ).
+		      '-'
+		      'trace'
+		      'trap'
+		      'untrace / untrap'
+		     )
+	  selectors:#(
+		      nil
+		      trace
+		      trap
+		      untrace
+		     ).
 
     menu actionAt:#untrace put:[self doUntrace:inst].
 
     args := Array new:2 withAll:inst.
     lbls := Array with:'message'
-                  with:((Text string:' all ' emphasis:#underline), ' messages').
+		  with:((Text string:' all ' emphasis:#underline), ' messages').
 
     menu subMenuAt:#trace put:(
-        PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
+	PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
     ).
 
     menu subMenuAt:#trap put:(
-        PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
+	PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
     ).
 
   ^ menu
@@ -576,16 +576,16 @@
     index   := listViews findLast:[:v|v == list].
 
     (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[
-        index := index + 1.
-        (list selectedInstanceType) == #directory ifTrue:[
-            (listViews at:index) inspect:instVar
-        ] ifFalse:[
-            (listViews at:index) inspect:nil
-        ].
-        self update
+	index := index + 1.
+	(list selectedInstanceType) == #directory ifTrue:[
+	    (listViews at:index) inspect:instVar
+	] ifFalse:[
+	    (listViews at:index) inspect:nil
+	].
+	self update
     ].
     valueChangedAction notNil ifTrue:[
-        valueChangedAction value:instVar
+	valueChangedAction value:instVar
     ].
     ^ result
 !
@@ -597,16 +597,16 @@
     |index|
 
     rightHistory notEmpty ifTrue:[
-        ^ rightHistory first
+	^ rightHistory first
     ].
     index := listViews findLast:[:v| v hasSelection ].
 
     index ~~ 0 ifTrue:[
-        ^ listViews at:index
+	^ listViews at:index
     ].
 
     leftHistory notEmpty ifTrue:[^ leftHistory last]
-                        ifFalse:[^ listViews at:1]
+			ifFalse:[^ listViews at:1]
 !
 
 update
@@ -620,27 +620,27 @@
     stop  := listViews size.
 
     [   cview  := listViews at:index.
-        ispObj := cview inspectedObject.
-        label  := labelViews at:index.
-        index  := index + 1.
+	ispObj := cview inspectedObject.
+	label  := labelViews at:index.
+	index  := index + 1.
 
-        ispObj notNil ifTrue:[
-            label label:(ispObj class name asString).
-            pview := cview.
-        ] ifFalse:[
-            [index <= stop] whileTrue:[
-                (labelViews at:index) label:''.
-                index := index + 1
-            ].
+	ispObj notNil ifTrue:[
+	    label label:(ispObj class name asString).
+	    pview := cview.
+	] ifFalse:[
+	    [index <= stop] whileTrue:[
+		(labelViews at:index) label:''.
+		index := index + 1
+	    ].
 
-            (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
-                pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
-                label label:ispObj class name asString
-            ] ifFalse:[
-                label label:''
-            ]
-        ].
-        index > stop
+	    (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
+		pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
+		label label:ispObj class name asString
+	    ] ifFalse:[
+		label label:''
+	    ]
+	].
+	index > stop
 
     ] whileFalse.
 
@@ -649,7 +649,7 @@
     index := listViews size + leftHistory size + rightHistory size.
 
     (listViews last) selectedInstanceType notNil ifTrue:[
-        index := index + 1
+	index := index + 1
     ].
     scrollBar thumbHeight:(stop / index) * 100.
     scrollBar thumbOrigin:(100  / index * leftHistory size).
@@ -670,10 +670,10 @@
     newX   := 0.0.
 
     frames do:[:frame|
-        (newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
-        corn  := newX @ corn y.
-        frame origin:orig corner:corn.
-        orig  := newX @ orig y.
+	(newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
+	corn  := newX @ corn y.
+	frame origin:orig corner:corn.
+	orig  := newX @ orig y.
     ].
 
 
@@ -690,8 +690,8 @@
     label  leftInset:15.
     label rightInset:2.
 
-    view  := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20 
-                         corner:1.0@1.0 in:frame.
+    view  := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20
+			 corner:1.0@1.0 in:frame.
 
     view := view scrolledView.
 
@@ -702,7 +702,7 @@
     index := listViews size.
 
     index == 1 ifTrue:[
-        view includesSelf:true
+	view includesSelf:true
     ].
 
     label adjust:#left.
@@ -725,7 +725,7 @@
     |fView stop pView index|
 
     (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[
-        ^ self
+	^ self
     ].
 
     index := nTimes.
@@ -736,16 +736,16 @@
 
     [   leftHistory add:(fView list).
 
-        1 to:stop do:[:i|
-            (listViews at:i) list:(listViews at:(i+1))
-        ].
+	1 to:stop do:[:i|
+	    (listViews at:i) list:(listViews at:(i+1))
+	].
 
-        rightHistory notEmpty ifTrue:[
-            (listViews last) list:(rightHistory removeLast)
-        ] ifFalse:[
-            (listViews last) inspect:(pView selectedInstanceVar)
-        ].
-        ((index := index - 1) == 0 or:[listViews last isEmpty])
+	rightHistory notEmpty ifTrue:[
+	    (listViews last) list:(rightHistory removeLast)
+	] ifFalse:[
+	    (listViews last) inspect:(pView selectedInstanceVar)
+	].
+	((index := index - 1) == 0 or:[listViews last isEmpty])
 
     ] whileFalse.
 
@@ -763,23 +763,23 @@
     size := leftHistory size.
 
     (nTimes > 0 and:[size ~~ 0]) ifTrue:[
-        nTimes > size ifFalse:[index := nTimes]
-                       ifTrue:[index := size].
+	nTimes > size ifFalse:[index := nTimes]
+		       ifTrue:[index := size].
 
-        size  := listViews size.
-        lView := listViews last.
-        fView := listViews first.
+	size  := listViews size.
+	lView := listViews last.
+	fView := listViews first.
 
-        1 to:index do:[:i|
-            lView hasSelection ifTrue:[
-                rightHistory add:(lView list)
-            ].
-            size to:2 by:-1 do:[:i|
-                (listViews at:i) list:(listViews at:(i-1))
-            ].
-            fView list:(leftHistory removeLast)
-        ].
-        self update
+	1 to:index do:[:i|
+	    lView hasSelection ifTrue:[
+		rightHistory add:(lView list)
+	    ].
+	    size to:2 by:-1 do:[:i|
+		(listViews at:i) list:(listViews at:(i-1))
+	    ].
+	    fView list:(leftHistory removeLast)
+	].
+	self update
     ]
 
 !
@@ -792,7 +792,7 @@
     noScr := listViews size + leftHistory size + rightHistory size.
 
     (listViews last) selectedInstanceType notNil ifTrue:[
-        noScr := noScr + 1
+	noScr := noScr + 1
     ].
     dY := 100 / noScr.
     pR := nPercent roundTo:dY.
@@ -800,11 +800,11 @@
     no := ((dY * leftHistory size) - pR) / dY.
 
     no == 0 ifTrue:[
-        (nPercent - pR) > 0 ifTrue:[no := -1]
-                           ifFalse:[no :=  1]
+	(nPercent - pR) > 0 ifTrue:[no := -1]
+			   ifFalse:[no :=  1]
     ].
     no < 0 ifTrue:[self moveContentsLeft:(no negated)]
-          ifFalse:[self moveContentsRight:no]
+	  ifFalse:[self moveContentsRight:no]
 ! !
 
 !NewInspectorPanelView class methodsFor:'documentation'!