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