InspectorPanelView.st
changeset 35 6f1565819b63
child 39 03af455029eb
equal deleted inserted replaced
34:0f083a268b66 35:6f1565819b63
       
     1 "{ NameSpace: NewInspector }"
       
     2 
       
     3 SimpleView subclass:#InspectorPanelView
       
     4 	instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory
       
     5 		rightHistory hzpView actionBlock valueChangedAction'
       
     6 	classVariableNames:''
       
     7 	poolDictionaries:''
       
     8 	category:'Inspector'
       
     9 !
       
    10 
       
    11 !InspectorPanelView class methodsFor:'documentation'!
       
    12 
       
    13 examples
       
    14 "
       
    15     example 1
       
    16     =========
       
    17 
       
    18     |top slv|
       
    19 
       
    20     top := StandardSystemView new extent:600@400.
       
    21     slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
       
    22     slv inspect:top.
       
    23     slv action:[:el|Transcript showCR:el].
       
    24     top open.
       
    25 
       
    26 
       
    27     example 2
       
    28     =========
       
    29 
       
    30     |top slv edt a vvp|
       
    31 
       
    32     a := Array new:5.
       
    33     a at:4 put:(Array new:6).
       
    34 
       
    35     top := StandardSystemView new extent:600@400.
       
    36     vvp := VariableVerticalPanel origin:0.0@0.0  corner:1.0@1.0 in:top.
       
    37 
       
    38     slv := NewInspector::InspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp.
       
    39     edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp.
       
    40     edt acceptAction:[:theText|slv accept:theText notifying:edt].
       
    41     edt   doItAction:[:theCode|slv doIt:theCode   notifying:edt].
       
    42 
       
    43     slv action:[:el| Transcript showCR:(el printString)].
       
    44     slv inspect:a.
       
    45 
       
    46     top open.
       
    47 
       
    48 
       
    49 
       
    50 "
       
    51 ! !
       
    52 
       
    53 !InspectorPanelView class methodsFor:'constants'!
       
    54 
       
    55 minDepth
       
    56     "returns the maximum of views
       
    57     "
       
    58     ^ 4
       
    59 ! !
       
    60 
       
    61 !InspectorPanelView methodsFor:'accessing'!
       
    62 
       
    63 depth
       
    64     "returns number of listViews
       
    65     "
       
    66   ^ listViews size
       
    67 !
       
    68 
       
    69 depth:aDepth
       
    70     "change the number of existing listViews
       
    71     "
       
    72     |sz min|
       
    73 
       
    74     min := self class minDepth.
       
    75 
       
    76     aDepth > min ifTrue:[
       
    77         sz := aDepth min:maxDepth.
       
    78 
       
    79         sz < listViews size ifTrue:[
       
    80             sz := listViews size
       
    81         ]
       
    82     ] ifFalse:[
       
    83         sz := min
       
    84     ].
       
    85 
       
    86     listViews size == sz ifTrue:[
       
    87         sz == aDepth ifFalse:[self moveContentsLeft:1].
       
    88     ] ifFalse:[
       
    89         [self createViewWithoutRedraw. listViews size ~~ sz] whileTrue.
       
    90         self computeExtentOfFrames.
       
    91 
       
    92         (self topView shown) ifTrue:[
       
    93             hzpView sizeChanged:nil.
       
    94             hzpView realizeAllSubViews.
       
    95         ]
       
    96     ]
       
    97 !
       
    98 
       
    99 maxDepth
       
   100     ^ maxDepth
       
   101 !
       
   102 
       
   103 maxDepth:aNumber
       
   104     "change max depth for instance
       
   105     "
       
   106     aNumber > listViews size ifTrue:[
       
   107         aNumber >= (self class minDepth) ifTrue:[
       
   108             maxDepth := aNumber.
       
   109 
       
   110             maxDepth < listViews size ifTrue:[
       
   111                 self depth:maxDepth
       
   112             ]
       
   113         ]
       
   114     ]
       
   115 ! !
       
   116 
       
   117 !InspectorPanelView methodsFor:'accessing actions'!
       
   118 
       
   119 action:aOneArgBlock
       
   120     "set the single click action block.
       
   121      If non-nil, that one is evaluated on single click, passing the
       
   122      selected instance as argument
       
   123     "
       
   124     actionBlock := aOneArgBlock
       
   125 
       
   126 
       
   127 !
       
   128 
       
   129 valueChangedAction:aOneArgBlock
       
   130     "evaluated if an instnace changed its value; passing
       
   131      the instance as argument
       
   132     "
       
   133     valueChangedAction := aOneArgBlock
       
   134 ! !
       
   135 
       
   136 !InspectorPanelView methodsFor:'accessing selections'!
       
   137 
       
   138 inspectedObject
       
   139     "returns the current inspected object
       
   140     "
       
   141     |i el|
       
   142 
       
   143     rightHistory notEmpty ifTrue:[
       
   144         el := rightHistory last
       
   145     ] ifFalse:[
       
   146         el := listViews findLast:[:v|v hasSelection].
       
   147         el := listViews at:el.
       
   148     ].
       
   149     ^ el inspectedObject
       
   150 !
       
   151 
       
   152 selectedInstanceVar
       
   153     "returns the current selected instance var
       
   154     "
       
   155     |el|
       
   156 
       
   157     rightHistory notEmpty ifTrue:[
       
   158         el := rightHistory last
       
   159     ] ifFalse:[
       
   160         el := listViews findLast:[:v|v hasSelection].
       
   161         el := listViews at:el
       
   162     ].
       
   163     ^ el selectedInstanceVar
       
   164 ! !
       
   165 
       
   166 !InspectorPanelView methodsFor:'actions'!
       
   167 
       
   168 accept:aText notifying:aView
       
   169     self doItOrAccept:[:v|v accept:aText notifying:aView]
       
   170 !
       
   171 
       
   172 doIt:aCode notifying:aView
       
   173     ^ self doItOrAccept:[:v|v doIt:aCode notifying:aView]
       
   174 !
       
   175 
       
   176 inspect:anObject
       
   177     "change the inspected object
       
   178     "
       
   179     |view|
       
   180 
       
   181     view := listViews first.
       
   182     leftHistory  removeAll.
       
   183     rightHistory removeAll.
       
   184 
       
   185     view inspect:anObject.
       
   186     listViews from:2 do:[:v|v inspect:nil].
       
   187     self update.
       
   188 ! !
       
   189 
       
   190 !InspectorPanelView methodsFor:'event handling'!
       
   191 
       
   192 handlesKeyPress:key inView:someView
       
   193     ^ true
       
   194 
       
   195 !
       
   196 
       
   197 keyPress:key x:x y:y view:someView
       
   198 
       
   199     key == #CursorLeft  ifTrue:[^ self moveContentsRight:1].
       
   200     key == #CursorRight ifTrue:[^ self moveContentsLeft:1 ].
       
   201 
       
   202     someView keyPress:key x:x y:y.
       
   203 
       
   204 !
       
   205 
       
   206 singleClickAt:anIndex
       
   207     "the view changed its selection caused by a single click
       
   208     "
       
   209     |view start sivar|
       
   210 
       
   211     rightHistory removeAll.
       
   212 
       
   213     view  := listViews at:anIndex.
       
   214     start := anIndex + 1.
       
   215     sivar := view selectedInstanceVar.
       
   216 
       
   217     start > listViews size ifTrue:[
       
   218         start >= maxDepth ifTrue:[
       
   219             self moveContentsLeft:1.
       
   220           ^ actionBlock value:sivar.
       
   221         ].
       
   222     ].
       
   223 
       
   224     (view selectedInstanceType) == #directory ifTrue:[
       
   225         (listViews at:start) setSelection:nil.
       
   226         (listViews at:start) inspect:sivar.
       
   227         
       
   228         start := start + 1.
       
   229     ].
       
   230 
       
   231     listViews from:start do:[:v|v inspect:nil].
       
   232     self update.
       
   233     actionBlock value:sivar.
       
   234 ! !
       
   235 
       
   236 !InspectorPanelView methodsFor:'initializing'!
       
   237 
       
   238 initialize
       
   239     "initialize instance
       
   240     "
       
   241     super initialize.
       
   242 
       
   243     frames       := OrderedCollection new.
       
   244     listViews    := OrderedCollection new.
       
   245     labelViews   := OrderedCollection new.
       
   246     leftHistory  := OrderedCollection new.
       
   247     rightHistory := OrderedCollection new.
       
   248     maxDepth     := self class minDepth.
       
   249 
       
   250     actionBlock := [:el| ].
       
   251 
       
   252     hzpView    := VariableHorizontalPanel origin:0.0@0.0 corner:1.0@1.0 in:self.
       
   253     scrollBar  := HorizontalScrollBar origin:0.0@1.0 corner:1.0@1.0 in:self.
       
   254     scrollBar asynchronousOperation.
       
   255 
       
   256     hzpView bottomInset:(scrollBar preferredExtent y).
       
   257 
       
   258     scrollBar topInset:(scrollBar preferredExtent y) negated.
       
   259     scrollBar thumbHeight:100.
       
   260     scrollBar scrollAction:[:percent | self scrollTo:percent].
       
   261     scrollBar scrollRightAction:[self moveContentsLeft:1].
       
   262     scrollBar scrollLeftAction:[self moveContentsRight:1].
       
   263 
       
   264     self depth:maxDepth.
       
   265 ! !
       
   266 
       
   267 !InspectorPanelView methodsFor:'menu - labels & actions'!
       
   268 
       
   269 browse:anIndex
       
   270     self classAtLabel:anIndex do:[:cls| cls browserClass openInClass:cls selector:nil ]
       
   271 
       
   272 !
       
   273 
       
   274 browseClassHierarchy:anIndex
       
   275     self classAtLabel:anIndex do:[:cls| cls browserClass browseClassHierarchy:cls ]
       
   276 
       
   277 !
       
   278 
       
   279 browseFullClassProtocol:anIndex
       
   280     self classAtLabel:anIndex do:[:cls| cls browserClass browseFullClassProtocol:cls ]
       
   281 
       
   282 !
       
   283 
       
   284 classAtLabel:anIndex do:anAction
       
   285     "evaluate action on class assigned to label
       
   286     "
       
   287     |cls|
       
   288 
       
   289     anIndex <= labelViews size ifTrue:[
       
   290         (cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[
       
   291             anAction value:cls
       
   292         ]
       
   293     ]
       
   294 
       
   295 !
       
   296 
       
   297 labelMenu
       
   298     "popup menu required by any label. Delegate the request to the corresponding label
       
   299     "
       
   300     |sqNr view|
       
   301 
       
   302     view := (WindowGroup lastEventQuerySignal raise) view.
       
   303     sqNr := labelViews findFirst:[:v| v == view].
       
   304 
       
   305     sqNr ~~ 0 ifTrue:[
       
   306         view := labelViews at:sqNr.
       
   307 
       
   308         view label notEmpty ifTrue:[
       
   309             ^ self labelMenu:sqNr
       
   310         ]
       
   311     ].
       
   312     ^ nil
       
   313 !
       
   314 
       
   315 labelMenu:anIndex
       
   316     "popup menu required for a label identified by its sequence number
       
   317     "
       
   318     |menu|
       
   319 
       
   320     menu := PopUpMenu labels:#(
       
   321                               'browse'
       
   322                               'browse class hierarchy'
       
   323                               'browse full class protocol'
       
   324                               )
       
   325                    selectors:#( 
       
   326                               browse:
       
   327                               browseClassHierarchy:
       
   328                               browseFullClassProtocol:
       
   329                               )
       
   330                     receiver:self.
       
   331 
       
   332    menu args:(Array new:(menu labels size) withAll:anIndex).
       
   333  ^ menu
       
   334 
       
   335 ! !
       
   336 
       
   337 !InspectorPanelView methodsFor:'menu - views & actions'!
       
   338 
       
   339 doTrace:anInstance
       
   340     "place a trace on messages sent to the instance
       
   341     "
       
   342     |selectors|
       
   343 
       
   344     selectors := self messageMenu:anInstance.
       
   345 
       
   346     selectors notNil ifTrue:[
       
   347         self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors]
       
   348     ].
       
   349 
       
   350 !
       
   351 
       
   352 doTraceAll:anInstance
       
   353     "place a trace on all messages sent to the instance
       
   354     "
       
   355     self topView withWaitCursorDo:[MessageTracer traceAll:anInstance]
       
   356 !
       
   357 
       
   358 doTrap:anInstance
       
   359     "place a trap on a message sent to the instance
       
   360     "
       
   361     |selectors|
       
   362 
       
   363     selectors := self messageMenu:anInstance.
       
   364 
       
   365     selectors notNil ifTrue:[
       
   366         self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors]
       
   367     ]
       
   368 !
       
   369 
       
   370 doTrapAll:anInstance
       
   371     "place a trap on all messages sent to the instance
       
   372     "
       
   373     self topView withWaitCursorDo:[MessageTracer trapAll:anInstance]
       
   374 
       
   375 !
       
   376 
       
   377 doUntrace:anInstance
       
   378     "remove all traps and traces to the instance
       
   379     "
       
   380     self topView withWaitCursorDo:[MessageTracer untrace:anInstance].
       
   381 
       
   382 !
       
   383 
       
   384 messageMenu:anInstance
       
   385     "open menu to select messages; on accepted a list of messages is returned
       
   386     "
       
   387     |sll acl lst inset top hzp slv acv dblClcAct btp b1 b2 accepted viewSpacing|
       
   388 
       
   389     top := StandardSystemView new.
       
   390     top extent:500 @ 400.
       
   391     top label:(anInstance printString).
       
   392 
       
   393     (Label origin:(0.0 @  0.0) corner:(0.5 @ 20) in:top) label:'messages'.
       
   394     (Label origin:(0.5 @  0.0) corner:(1.0 @ 20) in:top) label:'selected'.
       
   395     hzp := VariableHorizontalPanel origin:(0.0 @ 20) corner:(1.0 @ 1.0) in:top.
       
   396     btp := HorizontalPanelView origin:(0.0 @1.0) corner:(1.0 @ 1.0) in:top.
       
   397 
       
   398     b1 := Button abortButtonIn:btp.
       
   399     b2 := Button okButtonIn:btp.
       
   400     accepted := false.
       
   401 
       
   402     b1 action:[accepted := false. top destroy].
       
   403     b2 action:[accepted := true.  top destroy].
       
   404 
       
   405     btp horizontalLayout:#fitSpace.
       
   406     viewSpacing := top class viewSpacing.
       
   407     inset       := (b2 preferredExtent y) + viewSpacing.
       
   408     viewSpacing := viewSpacing // 2.
       
   409 
       
   410     hzp bottomInset:inset.
       
   411     btp topInset:((inset - viewSpacing) negated).
       
   412     btp bottomInset:viewSpacing.
       
   413 
       
   414     slv := ScrollableView for:SelectionInListView
       
   415                 miniScrollerV:true
       
   416                        origin:(0.0 @ 0.0)
       
   417                        corner:(0.5 @ 1.0)
       
   418                            in:hzp.
       
   419 
       
   420     acv := ScrollableView for:SelectionInListView
       
   421                 miniScrollerV:true
       
   422                        origin:(0.5 @ 0.0)
       
   423                        corner:(1.0 @ 1.0)
       
   424                            in:hzp.
       
   425 
       
   426     slv := slv scrolledView.
       
   427     acv := acv scrolledView.
       
   428 
       
   429     sll := (MessageTracer realClassOf:anInstance) selectors.
       
   430     acl := OrderedCollection new.
       
   431 
       
   432     (MessageTracer wrappedSelectorsOf:anInstance) do:[:el|
       
   433         el notNil ifTrue:[
       
   434             acl add:el.
       
   435             sll remove:el ifAbsent:nil
       
   436         ]
       
   437     ].
       
   438         
       
   439     slv list:(sll copy).
       
   440     acv list:(acl copy).
       
   441 
       
   442     dblClcAct := [:from :to|
       
   443         to add:(from selectionValue).
       
   444         from removeIndex:(from selection).
       
   445         from redraw.
       
   446     ].
       
   447 
       
   448     slv doubleClickAction:[:index| dblClcAct value:slv value:acv].
       
   449     acv doubleClickAction:[:index| dblClcAct value:acv value:slv].
       
   450 
       
   451     top openModal.
       
   452 
       
   453     accepted ifFalse:[
       
   454         ^ nil
       
   455     ].
       
   456     lst := acv list.
       
   457 
       
   458 "undo existing traps            HACK: removes traps and traces"
       
   459 
       
   460     acl notEmpty ifTrue:[
       
   461         MessageTracer untrace:anInstance
       
   462     ].
       
   463 
       
   464     lst notEmpty ifTrue:[^ lst]
       
   465                 ifFalse:[^ nil]
       
   466 !
       
   467 
       
   468 viewMenu
       
   469     "popup menu required by any view. Delegate the request to the corresponding view
       
   470     "
       
   471     |sqNr view|
       
   472 
       
   473     view := (WindowGroup lastEventQuerySignal raise) view.
       
   474     sqNr := listViews findFirst:[:v| v == view].
       
   475 
       
   476     sqNr notNil ifTrue:[^ self viewMenu:sqNr]
       
   477                ifFalse:[^ nil]
       
   478 !
       
   479 
       
   480 viewMenu:anIndex
       
   481     "popup menu required for a view identified by its sequence number
       
   482     "
       
   483     |view menu inst args lbls txt|
       
   484 
       
   485     view := listViews at:anIndex.
       
   486     view hasSelection ifFalse:[^ nil].
       
   487     inst := view selectedInstanceVar.
       
   488 
       
   489     menu := PopUpMenu labels:#( 'update' '-')
       
   490                    selectors:#( #update  nil)
       
   491                     receiver:self.
       
   492 
       
   493     menu actionAt:#update put:[
       
   494         view updateList.
       
   495 
       
   496         listViews from:(anIndex + 1) do:[:v|
       
   497             (view selectedInstanceType) ~~ #directory ifTrue:[
       
   498                 v inspect:nil
       
   499             ] ifFalse:[
       
   500                 v inspect:(view selectedInstanceVar).
       
   501                 view := v.
       
   502             ]
       
   503         ].
       
   504         self update
       
   505     ].
       
   506 
       
   507     menu  addLabels:#(
       
   508                       'trace'
       
   509                       'trap'
       
   510                       'untrace / untrap'
       
   511                      )
       
   512           selectors:#(
       
   513                       trace
       
   514                       trap
       
   515                       untrace
       
   516                      ).
       
   517 
       
   518     menu actionAt:#untrace put:[self doUntrace:inst].
       
   519 
       
   520     args := Array new:2 withAll:inst.
       
   521     lbls := Array with:'message'
       
   522                   with:((Text string:' all ' emphasis:#underline), ' messages').
       
   523 
       
   524     menu subMenuAt:#trace put:(
       
   525         PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args
       
   526     ).
       
   527 
       
   528     menu subMenuAt:#trap put:(
       
   529         PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args
       
   530     ).
       
   531 
       
   532   ^ menu
       
   533 
       
   534 
       
   535 ! !
       
   536 
       
   537 !InspectorPanelView methodsFor:'private'!
       
   538 
       
   539 doItOrAccept:aBlock
       
   540     "handle a doIt or accept action
       
   541     "
       
   542     |index view ivar rslt last stop|
       
   543 
       
   544     last := listViews last.
       
   545     self moveContentsLeft:(rightHistory size).
       
   546 
       
   547     last hasSelection ifTrue:[
       
   548         self moveContentsLeft:1.
       
   549         index := (listViews size) - 1
       
   550     ] ifFalse:[
       
   551         index := listViews findLast:[:v|v hasSelection].
       
   552     ].
       
   553 
       
   554     index ~~ 0 ifTrue:[
       
   555         view := listViews at:index.
       
   556         rslt := aBlock value:view.
       
   557         stop := listViews size.
       
   558         ivar := view selectedInstanceVar.
       
   559 
       
   560         index == stop ifTrue:[
       
   561             self moveContentsLeft:1.
       
   562         ] ifFalse:[
       
   563             index := index + 1.
       
   564 
       
   565             (view selectedInstanceType) == #directory ifTrue:[
       
   566                 (listViews at:index) inspect:ivar
       
   567             ] ifFalse:[
       
   568                 (listViews at:index) inspect:nil
       
   569             ].
       
   570             self update.
       
   571         ].
       
   572 
       
   573         valueChangedAction notNil ifTrue:[
       
   574             valueChangedAction value:ivar
       
   575         ]
       
   576     ].
       
   577     ^ rslt
       
   578 !
       
   579 
       
   580 update
       
   581     "update labels and scrollbar
       
   582     "
       
   583     |pview cview stop index ispObj label|
       
   584 
       
   585 "UPDATE LABELS
       
   586 "
       
   587     index := 1.
       
   588     stop  := listViews size.
       
   589 
       
   590     [   cview  := listViews at:index.
       
   591         ispObj := cview inspectedObject.
       
   592         label  := labelViews at:index.
       
   593         index  := index + 1.
       
   594 
       
   595         ispObj notNil ifTrue:[
       
   596             label label:(ispObj class name asString).
       
   597             pview := cview.
       
   598         ] ifFalse:[
       
   599             [index <= stop] whileTrue:[
       
   600                 (labelViews at:index) label:''.
       
   601                 index := index + 1
       
   602             ].
       
   603 
       
   604             (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[
       
   605                 pview notNil ifTrue:[ispObj := pview selectedInstanceVar].
       
   606                 label label:ispObj class name asString
       
   607             ] ifFalse:[
       
   608                 label label:''
       
   609             ]
       
   610         ].
       
   611         index > stop
       
   612 
       
   613     ] whileFalse.
       
   614 
       
   615 "UPDATE SCROLLBARS
       
   616 "
       
   617     index := listViews size + leftHistory size + rightHistory size.
       
   618 
       
   619     (listViews last) selectedInstanceType notNil ifTrue:[
       
   620         index := index + 1
       
   621     ].
       
   622     scrollBar thumbHeight:(stop / index) * 100.
       
   623     scrollBar thumbOrigin:(100  / index * leftHistory size).
       
   624 
       
   625 ! !
       
   626 
       
   627 !InspectorPanelView methodsFor:'private frames'!
       
   628 
       
   629 computeExtentOfFrames
       
   630     "compute the extent of all frames (origin/corner)
       
   631     "
       
   632     |orig corn offset newX|
       
   633 
       
   634     orig := ( 0.0 @ 0.0 ).
       
   635     corn := ( 0.0 @ 1.0 ).
       
   636 
       
   637     offset := 1.0 / (frames size).
       
   638     newX   := 0.0.
       
   639 
       
   640     frames do:[:frame|
       
   641         (newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ].
       
   642         corn  := newX @ corn y.
       
   643         frame origin:orig corner:corn.
       
   644         orig  := newX @ orig y.
       
   645     ].
       
   646 
       
   647 
       
   648 !
       
   649 
       
   650 createViewWithoutRedraw
       
   651     "add a new view at end
       
   652     "
       
   653     |view frame label index|
       
   654 
       
   655     frame := SimpleView in:hzpView.
       
   656 
       
   657     label := Label origin:0.0@0.0 corner:1.0@20 in:frame.
       
   658     label  leftInset:15.
       
   659     label rightInset:2.
       
   660 
       
   661     view  := ScrollableView for:InspectorListView miniScroller:true origin:0.0@20 
       
   662                          corner:1.0@1.0 in:frame.
       
   663 
       
   664     view := view scrolledView.
       
   665 
       
   666     frames add:frame.
       
   667     labelViews add:label.
       
   668     listViews  add:view.
       
   669 
       
   670     index := listViews size.
       
   671 
       
   672     index == 1 ifTrue:[
       
   673         view includesSelf:true
       
   674     ].
       
   675 
       
   676     label adjust:#left.
       
   677     label label:''.
       
   678     label level:1.
       
   679     label menuHolder:self; menuMessage:#labelMenu; menuPerformer:self.
       
   680 
       
   681     view action:[:el|self singleClickAt:index].
       
   682 
       
   683     view delegate:self.
       
   684     view menuHolder:self; menuMessage:#viewMenu; menuPerformer:self.
       
   685 
       
   686 ! !
       
   687 
       
   688 !InspectorPanelView methodsFor:'scrolling-basic'!
       
   689 
       
   690 moveContentsLeft:nTimes
       
   691     "move the contents of each view one position left
       
   692     "
       
   693     |fView stop assoc inspObj pView index|
       
   694 
       
   695     (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[
       
   696         ^ self
       
   697     ].
       
   698 
       
   699     index := nTimes.
       
   700     stop  := (listViews size) - 1.
       
   701     fView := listViews first.
       
   702     pView := listViews at:stop.
       
   703 
       
   704 
       
   705     [   leftHistory add:fView listHolder.
       
   706 
       
   707         1 to:stop do:[:i|
       
   708             (listViews at:i) updateFromView:(listViews at:(i+1))
       
   709         ].
       
   710 
       
   711         rightHistory notEmpty ifTrue:[
       
   712             (listViews last) updateFromList:(rightHistory removeLast)
       
   713         ] ifFalse:[
       
   714             (listViews last) inspect:(pView selectedInstanceVar)
       
   715         ].
       
   716         ((index := index - 1) == 0 or:[listViews last isEmpty])
       
   717 
       
   718     ] whileFalse.
       
   719 
       
   720     self update.
       
   721 
       
   722 
       
   723 
       
   724 !
       
   725 
       
   726 moveContentsRight:nTimes
       
   727     "move the contents of all listViews one position right
       
   728     "
       
   729     |view assoc size index lView fView|
       
   730 
       
   731     size := leftHistory size.
       
   732 
       
   733     (nTimes > 0 and:[size ~~ 0]) ifTrue:[
       
   734         nTimes > size ifFalse:[index := nTimes]
       
   735                        ifTrue:[index := size].
       
   736 
       
   737         size  := listViews size.
       
   738         lView := listViews last.
       
   739         fView := listViews first.
       
   740 
       
   741         1 to:index do:[:i|
       
   742             lView hasSelection ifTrue:[
       
   743                 rightHistory add:(lView listHolder)
       
   744             ].
       
   745             size to:2 by:-1 do:[:i|
       
   746                 (listViews at:i) updateFromView:(listViews at:(i-1))
       
   747             ].
       
   748             fView updateFromList:(leftHistory removeLast)
       
   749         ].
       
   750         self update
       
   751     ]
       
   752 
       
   753 !
       
   754 
       
   755 scrollTo:nPercent
       
   756     "set views dependant on scroll bar
       
   757     "
       
   758     |dY no noScr pR|
       
   759 
       
   760     noScr := listViews size + leftHistory size + rightHistory size.
       
   761 
       
   762     (listViews last) selectedInstanceType notNil ifTrue:[
       
   763         noScr := noScr + 1
       
   764     ].
       
   765     dY := 100 / noScr.
       
   766     pR := nPercent roundTo:dY.
       
   767 
       
   768     no := ((dY * leftHistory size) - pR) / dY.
       
   769 
       
   770     no == 0 ifTrue:[
       
   771         (nPercent - pR) > 0 ifTrue:[no := -1]
       
   772                            ifFalse:[no :=  1]
       
   773     ].
       
   774     no < 0 ifTrue:[self moveContentsLeft:(no negated)]
       
   775           ifFalse:[self moveContentsRight:no]
       
   776 ! !
       
   777 
       
   778 !InspectorPanelView class methodsFor:'documentation'!
       
   779 
       
   780 version
       
   781     ^ '$Header$'
       
   782 ! !