NewInspectorPanelView.st
changeset 2621 285fa261cbcb
parent 2299 fff41ffaaf26
equal deleted inserted replaced
2620:fccbd77a9409 2621:285fa261cbcb
     1 "
     1 "
     2  COPYRIGHT (c) 1997 by eXept Software AG
     2  COPYRIGHT (c) 1997 by eXept Software AG
     3               All Rights Reserved
     3 	      All Rights Reserved
     4 
     4 
     5  This software is furnished under a license and may be used
     5  This software is furnished under a license and may be used
     6  only in accordance with the terms of that license and with the
     6  only in accordance with the terms of that license and with the
     7  inclusion of the above copyright notice.   This software may not
     7  inclusion of the above copyright notice.   This software may not
     8  be provided or otherwise made available to, or used by, any
     8  be provided or otherwise made available to, or used by, any
     9  other person.  No title to or ownership of the software is
     9  other person.  No title to or ownership of the software is
    10  hereby transferred.
    10  hereby transferred.
    11 "
    11 "
    12 "{ Package: 'stx:libtool2' }"
    12 "{ Package: 'stx:libtool2' }"
    13 
    13 
    14 "{ NameSpace: NewInspector }"
    14 "{ NameSpace: Tools }"
    15 
    15 
    16 SimpleView subclass:#NewInspectorPanelView
    16 SimpleView subclass:#NewInspectorPanelView
    17 	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
    17 	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
    18 		rightHistory hzpView actionBlock valueChangedAction'
    18 		rightHistory hzpView actionBlock valueChangedAction'
    19 	classVariableNames:''
    19 	classVariableNames:''
    24 !NewInspectorPanelView class methodsFor:'documentation'!
    24 !NewInspectorPanelView class methodsFor:'documentation'!
    25 
    25 
    26 copyright
    26 copyright
    27 "
    27 "
    28  COPYRIGHT (c) 1997 by eXept Software AG
    28  COPYRIGHT (c) 1997 by eXept Software AG
    29               All Rights Reserved
    29 	      All Rights Reserved
    30 
    30 
    31  This software is furnished under a license and may be used
    31  This software is furnished under a license and may be used
    32  only in accordance with the terms of that license and with the
    32  only in accordance with the terms of that license and with the
    33  inclusion of the above copyright notice.   This software may not
    33  inclusion of the above copyright notice.   This software may not
    34  be provided or otherwise made available to, or used by, any
    34  be provided or otherwise made available to, or used by, any
    42 examples
    42 examples
    43 "
    43 "
    44     example 1
    44     example 1
    45     =========
    45     =========
    46 
    46 
    47                                                                         [exBegin]
    47 									[exBegin]
    48     |top slv|
    48     |top slv|
    49 
    49 
    50     top := StandardSystemView new extent:600@400.
    50     top := StandardSystemView new extent:600@400.
    51     slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
    51     slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
    52     slv inspect:top.
    52     slv inspect:top.
    53     slv action:[:el|Transcript showCR:el].
    53     slv action:[:el|Transcript showCR:el].
    54     top open.
    54     top open.
    55                                                                         [exEnd]
    55 									[exEnd]
    56 
    56 
    57 
    57 
    58     example 2
    58     example 2
    59     =========
    59     =========
    60                                                                         [exBegin]
    60 									[exBegin]
    61     |top slv edt a vvp|
    61     |top slv edt a vvp|
    62 
    62 
    63     a := Array new:5.
    63     a := Array new:5.
    64     a at:4 put:(Array new:6).
    64     a at:4 put:(Array new:6).
    65 
    65 
    66     top := StandardSystemView new extent:600@400.
    66     top := StandardSystemView new extent:600@400.
    67     vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
    67     vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
    68 
    68 
    69     slv := NewInspector::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
    69     slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
    70     edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
    70     edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
    71     edt acceptAction:[:theText|slv accept:theText notifying:edt].
    71     edt acceptAction:[:theText|slv accept:theText notifying:edt].
    72     edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
    72     edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
    73 
    73 
    74     slv action:[:el| Transcript showCR:(el printString)].
    74     slv action:[:el| Transcript showCR:(el printString)].
    75     slv inspect:a.
    75     slv inspect:a.
    76 
    76 
    77     top open.
    77     top open.
    78                                                                         [exEnd]
    78 									[exEnd]
    79 "
    79 "
    80 ! !
    80 ! !
    81 
    81 
    82 !NewInspectorPanelView class methodsFor:'constants'!
    82 !NewInspectorPanelView class methodsFor:'constants'!
    83 
    83 
   101     |sz min|
   101     |sz min|
   102 
   102 
   103     min := self class minDepth.
   103     min := self class minDepth.
   104 
   104 
   105     aDepth > min ifTrue:[
   105     aDepth > min ifTrue:[
   106         sz := aDepth min:maxDepth.
   106 	sz := aDepth min:maxDepth.
   107 
   107 
   108         sz < listViews size ifTrue:[
   108 	sz < listViews size ifTrue:[
   109             sz := listViews size
   109 	    sz := listViews size
   110         ]
   110 	]
   111     ] ifFalse:[
   111     ] ifFalse:[
   112         sz := min
   112 	sz := min
   113     ].
   113     ].
   114 
   114 
   115     listViews size == sz ifTrue:[
   115     listViews size == sz ifTrue:[
   116         sz == aDepth ifFalse:[self moveContentsLeft:1].
   116 	sz == aDepth ifFalse:[self moveContentsLeft:1].
   117     ] ifFalse:[
   117     ] ifFalse:[
   118         [self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
   118 	[self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
   119         self computeExtentOfFrames.
   119 	self computeExtentOfFrames.
   120 
   120 
   121         (self topView shown) ifTrue:[
   121 	(self topView shown) ifTrue:[
   122             hzpView sizeChanged:nil.
   122 	    hzpView sizeChanged:nil.
   123             hzpView realizeAllSubViews.
   123 	    hzpView realizeAllSubViews.
   124         ]
   124 	]
   125     ]
   125     ]
   126 !
   126 !
   127 
   127 
   128 maxDepth
   128 maxDepth
   129     ^ maxDepth
   129     ^ maxDepth
   131 
   131 
   132 maxDepth:aNumber
   132 maxDepth:aNumber
   133     "change max depth for instance
   133     "change max depth for instance
   134     "
   134     "
   135     aNumber > listViews size ifTrue:[
   135     aNumber > listViews size ifTrue:[
   136         aNumber >= (self class minDepth) ifTrue:[
   136 	aNumber >= (self class minDepth) ifTrue:[
   137             maxDepth := aNumber.
   137 	    maxDepth := aNumber.
   138 
   138 
   139             maxDepth < listViews size ifTrue:[
   139 	    maxDepth < listViews size ifTrue:[
   140                 self depth:maxDepth
   140 		self depth:maxDepth
   141             ]
   141 	    ]
   142         ]
   142 	]
   143     ]
   143     ]
   144 ! !
   144 ! !
   145 
   145 
   146 !NewInspectorPanelView methodsFor:'accessing actions'!
   146 !NewInspectorPanelView methodsFor:'accessing actions'!
   147 
   147 
   235     view  := listViews at:anIndex.
   235     view  := listViews at:anIndex.
   236     start := anIndex + 1.
   236     start := anIndex + 1.
   237     sivar := view selectedInstanceVar.
   237     sivar := view selectedInstanceVar.
   238 
   238 
   239     start > listViews size ifTrue:[
   239     start > listViews size ifTrue:[
   240         start >= maxDepth ifTrue:[
   240 	start >= maxDepth ifTrue:[
   241             self moveContentsLeft:1.
   241 	    self moveContentsLeft:1.
   242           ^ actionBlock value:sivar.
   242 	  ^ actionBlock value:sivar.
   243         ].
   243 	].
   244     ].
   244     ].
   245 
   245 
   246     (view selectedInstanceType) == #directory ifTrue:[
   246     (view selectedInstanceType) == #directory ifTrue:[
   247         (listViews at:start) setSelection:nil.
   247 	(listViews at:start) setSelection:nil.
   248         (listViews at:start) inspect:sivar.
   248 	(listViews at:start) inspect:sivar.
   249         
   249 
   250         start := start + 1.
   250 	start := start + 1.
   251     ].
   251     ].
   252 
   252 
   253     listViews from:start do:[:v|v inspect:nil].
   253     listViews from:start do:[:v|v inspect:nil].
   254     self update.
   254     self update.
   255     actionBlock value:sivar.
   255     actionBlock value:sivar.
   307     "evaluate action on class assigned to label
   307     "evaluate action on class assigned to label
   308     "
   308     "
   309     |cls|
   309     |cls|
   310 
   310 
   311     anIndex <= labelViews size ifTrue:[
   311     anIndex <= labelViews size ifTrue:[
   312         (cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
   312 	(cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
   313             anAction value:cls
   313 	    anAction value:cls
   314         ]
   314 	]
   315     ]
   315     ]
   316 
   316 
   317 !
   317 !
   318 
   318 
   319 labelMenu
   319 labelMenu
   323 
   323 
   324     view := (WindowGroup lastEventQuerySignal query) view.
   324     view := (WindowGroup lastEventQuerySignal query) view.
   325     sqNr := labelViews findFirst:[:v| v == view].
   325     sqNr := labelViews findFirst:[:v| v == view].
   326 
   326 
   327     sqNr ~~ 0 ifTrue:[
   327     sqNr ~~ 0 ifTrue:[
   328         view := labelViews at:sqNr.
   328 	view := labelViews at:sqNr.
   329 
   329 
   330         view label notEmpty ifTrue:[
   330 	view label notEmpty ifTrue:[
   331             ^ self labelMenu:sqNr
   331 	    ^ self labelMenu:sqNr
   332         ]
   332 	]
   333     ].
   333     ].
   334     ^ nil
   334     ^ nil
   335 !
   335 !
   336 
   336 
   337 labelMenu:anIndex
   337 labelMenu:anIndex
   338     "popup menu required for a label identified by its sequence number
   338     "popup menu required for a label identified by its sequence number
   339     "
   339     "
   340     |menu|
   340     |menu|
   341 
   341 
   342     menu := PopUpMenu labels:#(
   342     menu := PopUpMenu labels:#(
   343                               'browse'
   343 			      'browse'
   344                               'browse class hierarchy'
   344 			      'browse class hierarchy'
   345                               'browse full class protocol'
   345 			      'browse full class protocol'
   346                               )
   346 			      )
   347                    selectors:#( 
   347 		   selectors:#(
   348                               browse:
   348 			      browse:
   349                               browseClassHierarchy:
   349 			      browseClassHierarchy:
   350                               browseFullClassProtocol:
   350 			      browseFullClassProtocol:
   351                               )
   351 			      )
   352                     receiver:self.
   352 		    receiver:self.
   353 
   353 
   354    menu args:(Array new:(menu labels size) withAll:anIndex).
   354    menu args:(Array new:(menu labels size) withAll:anIndex).
   355  ^ menu
   355  ^ menu
   356 
   356 
   357 ! !
   357 ! !
   364     |selectors|
   364     |selectors|
   365 
   365 
   366     selectors := self messageMenu:anInstance.
   366     selectors := self messageMenu:anInstance.
   367 
   367 
   368     selectors notNil ifTrue:[
   368     selectors notNil ifTrue:[
   369         self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
   369 	self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
   370     ].
   370     ].
   371 
   371 
   372 !
   372 !
   373 
   373 
   374 doTraceAll:anInstance
   374 doTraceAll:anInstance
   383     |selectors|
   383     |selectors|
   384 
   384 
   385     selectors := self messageMenu:anInstance.
   385     selectors := self messageMenu:anInstance.
   386 
   386 
   387     selectors notNil ifTrue:[
   387     selectors notNil ifTrue:[
   388         self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
   388 	self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
   389     ]
   389     ]
   390 !
   390 !
   391 
   391 
   392 doTrapAll:anInstance
   392 doTrapAll:anInstance
   393     "place a trap on all messages sent to the instance
   393     "place a trap on all messages sent to the instance
   432     hzp bottomInset:inset.
   432     hzp bottomInset:inset.
   433     btp topInset:((inset - viewSpacing) negated).
   433     btp topInset:((inset - viewSpacing) negated).
   434     btp bottomInset:viewSpacing.
   434     btp bottomInset:viewSpacing.
   435 
   435 
   436     slv := ScrollableView for:SelectionInListView
   436     slv := ScrollableView for:SelectionInListView
   437                 miniScrollerV:true
   437 		miniScrollerV:true
   438                        origin:(0.0 @ 0.0)
   438 		       origin:(0.0 @ 0.0)
   439                        corner:(0.5 @ 1.0)
   439 		       corner:(0.5 @ 1.0)
   440                            in:hzp.
   440 			   in:hzp.
   441 
   441 
   442     acv := ScrollableView for:SelectionInListView
   442     acv := ScrollableView for:SelectionInListView
   443                 miniScrollerV:true
   443 		miniScrollerV:true
   444                        origin:(0.5 @ 0.0)
   444 		       origin:(0.5 @ 0.0)
   445                        corner:(1.0 @ 1.0)
   445 		       corner:(1.0 @ 1.0)
   446                            in:hzp.
   446 			   in:hzp.
   447 
   447 
   448     slv := slv scrolledView.
   448     slv := slv scrolledView.
   449     acv := acv scrolledView.
   449     acv := acv scrolledView.
   450 
   450 
   451     sll := (MessageTracer realClassOf:anInstance) selectors.
   451     sll := (MessageTracer realClassOf:anInstance) selectors.
   452     acl := OrderedCollection new.
   452     acl := OrderedCollection new.
   453 
   453 
   454     (MessageTracer wrappedSelectorsOf:anInstance) do:[:el|
   454     (MessageTracer wrappedSelectorsOf:anInstance) do:[:el|
   455         el notNil ifTrue:[
   455 	el notNil ifTrue:[
   456             acl add:el.
   456 	    acl add:el.
   457             sll remove:el ifAbsent:nil
   457 	    sll remove:el ifAbsent:nil
   458         ]
   458 	]
   459     ].
   459     ].
   460         
   460 
   461     slv list:(sll copy).
   461     slv list:(sll copy).
   462     acv list:(acl copy).
   462     acv list:(acl copy).
   463 
   463 
   464     dblClcAct := [:from :to|
   464     dblClcAct := [:from :to|
   465         to add:(from selectionValue).
   465 	to add:(from selectionValue).
   466         from removeIndex:(from selection).
   466 	from removeIndex:(from selection).
   467         from redraw.
   467 	from redraw.
   468     ].
   468     ].
   469 
   469 
   470     slv doubleClickAction:[:index| dblClcAct value:slv value:acv].
   470     slv doubleClickAction:[:index| dblClcAct value:slv value:acv].
   471     acv doubleClickAction:[:index| dblClcAct value:acv value:slv].
   471     acv doubleClickAction:[:index| dblClcAct value:acv value:slv].
   472 
   472 
   473     top openModal.
   473     top openModal.
   474 
   474 
   475     accepted ifFalse:[
   475     accepted ifFalse:[
   476         ^ nil
   476 	^ nil
   477     ].
   477     ].
   478     lst := acv list.
   478     lst := acv list.
   479 
   479 
   480 "undo existing traps            HACK: removes traps and traces"
   480 "undo existing traps            HACK: removes traps and traces"
   481 
   481 
   482     acl notEmpty ifTrue:[
   482     acl notEmpty ifTrue:[
   483         MessageTracer untrace:anInstance
   483 	MessageTracer untrace:anInstance
   484     ].
   484     ].
   485 
   485 
   486     lst notEmpty ifTrue:[^ lst]
   486     lst notEmpty ifTrue:[^ lst]
   487                 ifFalse:[^ nil]
   487 		ifFalse:[^ nil]
   488 !
   488 !
   489 
   489 
   490 viewMenu
   490 viewMenu
   491     "popup menu required by any view. Delegate the request to the corresponding view
   491     "popup menu required by any view. Delegate the request to the corresponding view
   492     "
   492     "
   494 
   494 
   495     view := (WindowGroup lastEventQuerySignal query) view.
   495     view := (WindowGroup lastEventQuerySignal query) view.
   496     sqNr := listViews findFirst:[:v| v == view].
   496     sqNr := listViews findFirst:[:v| v == view].
   497 
   497 
   498     sqNr notNil ifTrue:[^ self viewMenu:sqNr]
   498     sqNr notNil ifTrue:[^ self viewMenu:sqNr]
   499                ifFalse:[^ nil]
   499 	       ifFalse:[^ nil]
   500 !
   500 !
   501 
   501 
   502 viewMenu:anIndex
   502 viewMenu:anIndex
   503     "popup menu required for a view identified by its sequence number
   503     "popup menu required for a view identified by its sequence number
   504     "
   504     "
   507     view := listViews at:anIndex.
   507     view := listViews at:anIndex.
   508     view hasSelection ifFalse:[^ nil].
   508     view hasSelection ifFalse:[^ nil].
   509     inst := view selectedInstanceVar.
   509     inst := view selectedInstanceVar.
   510 
   510 
   511     menu := PopUpMenu labels:#( 'update' )
   511     menu := PopUpMenu labels:#( 'update' )
   512                    selectors:#( #update  )
   512 		   selectors:#( #update  )
   513                     receiver:self.
   513 		    receiver:self.
   514 
   514 
   515     menu actionAt:#update put:[
   515     menu actionAt:#update put:[
   516         view update.
   516 	view update.
   517 
   517 
   518         listViews from:(anIndex + 1) do:[:v|
   518 	listViews from:(anIndex + 1) do:[:v|
   519             (view selectedInstanceType) ~~ #directory ifTrue:[
   519 	    (view selectedInstanceType) ~~ #directory ifTrue:[
   520                 v inspect:nil
   520 		v inspect:nil
   521             ] ifFalse:[
   521 	    ] ifFalse:[
   522                 v inspect:(view selectedInstanceVar).
   522 		v inspect:(view selectedInstanceVar).
   523                 view := v.
   523 		view := v.
   524             ]
   524 	    ]
   525         ].
   525 	].
   526         self update
   526 	self update
   527     ].
   527     ].
   528 
   528 
   529     (NewInspectorList isTraceable:inst) ifFalse:[
   529     (NewInspectorList isTraceable:inst) ifFalse:[
   530         ^ menu
   530 	^ menu
   531     ].
   531     ].
   532 
   532 
   533     menu  addLabels:#(
   533     menu  addLabels:#(
   534                       '-'
   534 		      '-'
   535                       'trace'
   535 		      'trace'
   536                       'trap'
   536 		      'trap'
   537                       'untrace / untrap'
   537 		      'untrace / untrap'
   538                      )
   538 		     )
   539           selectors:#(
   539 	  selectors:#(
   540                       nil
   540 		      nil
   541                       trace
   541 		      trace
   542                       trap
   542 		      trap
   543                       untrace
   543 		      untrace
   544                      ).
   544 		     ).
   545 
   545 
   546     menu actionAt:#untrace put:[self doUntrace:inst].
   546     menu actionAt:#untrace put:[self doUntrace:inst].
   547 
   547 
   548     args := Array new:2 withAll:inst.
   548     args := Array new:2 withAll:inst.
   549     lbls := Array with:'message'
   549     lbls := Array with:'message'
   550                   with:((Text string:' all ' emphasis:#underline), ' messages').
   550 		  with:((Text string:' all ' emphasis:#underline), ' messages').
   551 
   551 
   552     menu subMenuAt:#trace put:(
   552     menu subMenuAt:#trace put:(
   553         PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
   553 	PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
   554     ).
   554     ).
   555 
   555 
   556     menu subMenuAt:#trap put:(
   556     menu subMenuAt:#trap put:(
   557         PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
   557 	PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
   558     ).
   558     ).
   559 
   559 
   560   ^ menu
   560   ^ menu
   561 
   561 
   562 
   562 
   574     result  := aBlock value:list.
   574     result  := aBlock value:list.
   575     instVar := list selectedInstanceVar.
   575     instVar := list selectedInstanceVar.
   576     index   := listViews findLast:[:v|v == list].
   576     index   := listViews findLast:[:v|v == list].
   577 
   577 
   578     (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[
   578     (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[
   579         index := index + 1.
   579 	index := index + 1.
   580         (list selectedInstanceType) == #directory ifTrue:[
   580 	(list selectedInstanceType) == #directory ifTrue:[
   581             (listViews at:index) inspect:instVar
   581 	    (listViews at:index) inspect:instVar
   582         ] ifFalse:[
   582 	] ifFalse:[
   583             (listViews at:index) inspect:nil
   583 	    (listViews at:index) inspect:nil
   584         ].
   584 	].
   585         self update
   585 	self update
   586     ].
   586     ].
   587     valueChangedAction notNil ifTrue:[
   587     valueChangedAction notNil ifTrue:[
   588         valueChangedAction value:instVar
   588 	valueChangedAction value:instVar
   589     ].
   589     ].
   590     ^ result
   590     ^ result
   591 !
   591 !
   592 
   592 
   593 findLastValidListWithSelection
   593 findLastValidListWithSelection
   595      view, the list assigned to the inspected object is returned
   595      view, the list assigned to the inspected object is returned
   596     "
   596     "
   597     |index|
   597     |index|
   598 
   598 
   599     rightHistory notEmpty ifTrue:[
   599     rightHistory notEmpty ifTrue:[
   600         ^ rightHistory first
   600 	^ rightHistory first
   601     ].
   601     ].
   602     index := listViews findLast:[:v| v hasSelection ].
   602     index := listViews findLast:[:v| v hasSelection ].
   603 
   603 
   604     index ~~ 0 ifTrue:[
   604     index ~~ 0 ifTrue:[
   605         ^ listViews at:index
   605 	^ listViews at:index
   606     ].
   606     ].
   607 
   607 
   608     leftHistory notEmpty ifTrue:[^ leftHistory last]
   608     leftHistory notEmpty ifTrue:[^ leftHistory last]
   609                         ifFalse:[^ listViews at:1]
   609 			ifFalse:[^ listViews at:1]
   610 !
   610 !
   611 
   611 
   612 update
   612 update
   613     "update labels and scrollbar
   613     "update labels and scrollbar
   614     "
   614     "
   618 "
   618 "
   619     index := 1.
   619     index := 1.
   620     stop  := listViews size.
   620     stop  := listViews size.
   621 
   621 
   622     [   cview  := listViews at:index.
   622     [   cview  := listViews at:index.
   623         ispObj := cview inspectedObject.
   623 	ispObj := cview inspectedObject.
   624         label  := labelViews at:index.
   624 	label  := labelViews at:index.
   625         index  := index + 1.
   625 	index  := index + 1.
   626 
   626 
   627         ispObj notNil ifTrue:[
   627 	ispObj notNil ifTrue:[
   628             label label:(ispObj class name asString).
   628 	    label label:(ispObj class name asString).
   629             pview := cview.
   629 	    pview := cview.
   630         ] ifFalse:[
   630 	] ifFalse:[
   631             [index <= stop] whileTrue:[
   631 	    [index <= stop] whileTrue:[
   632                 (labelViews at:index) label:''.
   632 		(labelViews at:index) label:''.
   633                 index := index + 1
   633 		index := index + 1
   634             ].
   634 	    ].
   635 
   635 
   636             (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
   636 	    (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
   637                 pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
   637 		pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
   638                 label label:ispObj class name asString
   638 		label label:ispObj class name asString
   639             ] ifFalse:[
   639 	    ] ifFalse:[
   640                 label label:''
   640 		label label:''
   641             ]
   641 	    ]
   642         ].
   642 	].
   643         index > stop
   643 	index > stop
   644 
   644 
   645     ] whileFalse.
   645     ] whileFalse.
   646 
   646 
   647 "UPDATE SCROLLBARS
   647 "UPDATE SCROLLBARS
   648 "
   648 "
   649     index := listViews size + leftHistory size + rightHistory size.
   649     index := listViews size + leftHistory size + rightHistory size.
   650 
   650 
   651     (listViews last) selectedInstanceType notNil ifTrue:[
   651     (listViews last) selectedInstanceType notNil ifTrue:[
   652         index := index + 1
   652 	index := index + 1
   653     ].
   653     ].
   654     scrollBar thumbHeight:(stop / index) * 100.
   654     scrollBar thumbHeight:(stop / index) * 100.
   655     scrollBar thumbOrigin:(100  / index * leftHistory size).
   655     scrollBar thumbOrigin:(100  / index * leftHistory size).
   656 
   656 
   657 ! !
   657 ! !
   668 
   668 
   669     offset := 1.0 / (frames size).
   669     offset := 1.0 / (frames size).
   670     newX   := 0.0.
   670     newX   := 0.0.
   671 
   671 
   672     frames do:[:frame|
   672     frames do:[:frame|
   673         (newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
   673 	(newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
   674         corn  := newX @ corn y.
   674 	corn  := newX @ corn y.
   675         frame origin:orig corner:corn.
   675 	frame origin:orig corner:corn.
   676         orig  := newX @ orig y.
   676 	orig  := newX @ orig y.
   677     ].
   677     ].
   678 
   678 
   679 
   679 
   680 !
   680 !
   681 
   681 
   688 
   688 
   689     label := Label origin:0.0@0.0 corner:1.0@20 in:frame.
   689     label := Label origin:0.0@0.0 corner:1.0@20 in:frame.
   690     label  leftInset:15.
   690     label  leftInset:15.
   691     label rightInset:2.
   691     label rightInset:2.
   692 
   692 
   693     view  := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20 
   693     view  := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20
   694                          corner:1.0@1.0 in:frame.
   694 			 corner:1.0@1.0 in:frame.
   695 
   695 
   696     view := view scrolledView.
   696     view := view scrolledView.
   697 
   697 
   698     frames add:frame.
   698     frames add:frame.
   699     labelViews add:label.
   699     labelViews add:label.
   700     listViews  add:view.
   700     listViews  add:view.
   701 
   701 
   702     index := listViews size.
   702     index := listViews size.
   703 
   703 
   704     index == 1 ifTrue:[
   704     index == 1 ifTrue:[
   705         view includesSelf:true
   705 	view includesSelf:true
   706     ].
   706     ].
   707 
   707 
   708     label adjust:#left.
   708     label adjust:#left.
   709     label label:''.
   709     label label:''.
   710     label level:1.
   710     label level:1.
   723     "move the contents of all views one position left
   723     "move the contents of all views one position left
   724     "
   724     "
   725     |fView stop pView index|
   725     |fView stop pView index|
   726 
   726 
   727     (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[
   727     (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[
   728         ^ self
   728 	^ self
   729     ].
   729     ].
   730 
   730 
   731     index := nTimes.
   731     index := nTimes.
   732     stop  := (listViews size) - 1.
   732     stop  := (listViews size) - 1.
   733     fView := listViews first.
   733     fView := listViews first.
   734     pView := listViews at:stop.
   734     pView := listViews at:stop.
   735 
   735 
   736 
   736 
   737     [   leftHistory add:(fView list).
   737     [   leftHistory add:(fView list).
   738 
   738 
   739         1 to:stop do:[:i|
   739 	1 to:stop do:[:i|
   740             (listViews at:i) list:(listViews at:(i+1))
   740 	    (listViews at:i) list:(listViews at:(i+1))
   741         ].
   741 	].
   742 
   742 
   743         rightHistory notEmpty ifTrue:[
   743 	rightHistory notEmpty ifTrue:[
   744             (listViews last) list:(rightHistory removeLast)
   744 	    (listViews last) list:(rightHistory removeLast)
   745         ] ifFalse:[
   745 	] ifFalse:[
   746             (listViews last) inspect:(pView selectedInstanceVar)
   746 	    (listViews last) inspect:(pView selectedInstanceVar)
   747         ].
   747 	].
   748         ((index := index - 1) == 0 or:[listViews last isEmpty])
   748 	((index := index - 1) == 0 or:[listViews last isEmpty])
   749 
   749 
   750     ] whileFalse.
   750     ] whileFalse.
   751 
   751 
   752     self update.
   752     self update.
   753 
   753 
   761     |size index lView fView|
   761     |size index lView fView|
   762 
   762 
   763     size := leftHistory size.
   763     size := leftHistory size.
   764 
   764 
   765     (nTimes > 0 and:[size ~~ 0]) ifTrue:[
   765     (nTimes > 0 and:[size ~~ 0]) ifTrue:[
   766         nTimes > size ifFalse:[index := nTimes]
   766 	nTimes > size ifFalse:[index := nTimes]
   767                        ifTrue:[index := size].
   767 		       ifTrue:[index := size].
   768 
   768 
   769         size  := listViews size.
   769 	size  := listViews size.
   770         lView := listViews last.
   770 	lView := listViews last.
   771         fView := listViews first.
   771 	fView := listViews first.
   772 
   772 
   773         1 to:index do:[:i|
   773 	1 to:index do:[:i|
   774             lView hasSelection ifTrue:[
   774 	    lView hasSelection ifTrue:[
   775                 rightHistory add:(lView list)
   775 		rightHistory add:(lView list)
   776             ].
   776 	    ].
   777             size to:2 by:-1 do:[:i|
   777 	    size to:2 by:-1 do:[:i|
   778                 (listViews at:i) list:(listViews at:(i-1))
   778 		(listViews at:i) list:(listViews at:(i-1))
   779             ].
   779 	    ].
   780             fView list:(leftHistory removeLast)
   780 	    fView list:(leftHistory removeLast)
   781         ].
   781 	].
   782         self update
   782 	self update
   783     ]
   783     ]
   784 
   784 
   785 !
   785 !
   786 
   786 
   787 scrollTo:nPercent
   787 scrollTo:nPercent
   790     |dY no noScr pR|
   790     |dY no noScr pR|
   791 
   791 
   792     noScr := listViews size + leftHistory size + rightHistory size.
   792     noScr := listViews size + leftHistory size + rightHistory size.
   793 
   793 
   794     (listViews last) selectedInstanceType notNil ifTrue:[
   794     (listViews last) selectedInstanceType notNil ifTrue:[
   795         noScr := noScr + 1
   795 	noScr := noScr + 1
   796     ].
   796     ].
   797     dY := 100 / noScr.
   797     dY := 100 / noScr.
   798     pR := nPercent roundTo:dY.
   798     pR := nPercent roundTo:dY.
   799 
   799 
   800     no := ((dY * leftHistory size) - pR) / dY.
   800     no := ((dY * leftHistory size) - pR) / dY.
   801 
   801 
   802     no == 0 ifTrue:[
   802     no == 0 ifTrue:[
   803         (nPercent - pR) > 0 ifTrue:[no := -1]
   803 	(nPercent - pR) > 0 ifTrue:[no := -1]
   804                            ifFalse:[no :=  1]
   804 			   ifFalse:[no :=  1]
   805     ].
   805     ].
   806     no < 0 ifTrue:[self moveContentsLeft:(no negated)]
   806     no < 0 ifTrue:[self moveContentsLeft:(no negated)]
   807           ifFalse:[self moveContentsRight:no]
   807 	  ifFalse:[self moveContentsRight:no]
   808 ! !
   808 ! !
   809 
   809 
   810 !NewInspectorPanelView class methodsFor:'documentation'!
   810 !NewInspectorPanelView class methodsFor:'documentation'!
   811 
   811 
   812 version
   812 version