cg@809: " cg@809: COPYRIGHT (c) 1997 by eXept Software AG cg@2621: All Rights Reserved cg@809: cg@809: This software is furnished under a license and may be used cg@809: only in accordance with the terms of that license and with the cg@809: inclusion of the above copyright notice. This software may not cg@809: be provided or otherwise made available to, or used by, any cg@809: other person. No title to or ownership of the software is cg@809: hereby transferred. cg@809: " sv@2171: "{ Package: 'stx:libtool2' }" cg@809: cg@2621: "{ NameSpace: Tools }" ca@35: cg@1213: SimpleView subclass:#NewInspectorPanelView ca@35: instanceVariableNames:'frames labelViews listViews scrollBar maxDepth leftHistory ca@35: rightHistory hzpView actionBlock valueChangedAction' ca@35: classVariableNames:'' ca@35: poolDictionaries:'' cg@1213: category:'Interface-NewInspector' ca@35: ! ca@35: cg@1213: !NewInspectorPanelView class methodsFor:'documentation'! ca@35: cg@809: copyright cg@809: " cg@809: COPYRIGHT (c) 1997 by eXept Software AG cg@2621: All Rights Reserved cg@809: cg@809: This software is furnished under a license and may be used cg@809: only in accordance with the terms of that license and with the cg@809: inclusion of the above copyright notice. This software may not cg@809: be provided or otherwise made available to, or used by, any cg@809: other person. No title to or ownership of the software is cg@809: hereby transferred. cg@809: " cg@809: cg@809: cg@809: ! cg@809: ca@35: examples ca@35: " ca@35: example 1 ca@35: ========= ca@35: cg@2621: [exBegin] ca@35: |top slv| ca@35: ca@35: top := StandardSystemView new extent:600@400. cg@2621: slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@1.0 in:top. ca@35: slv inspect:top. ca@35: slv action:[:el|Transcript showCR:el]. ca@35: top open. cg@2621: [exEnd] ca@35: ca@35: ca@35: example 2 ca@35: ========= cg@2621: [exBegin] ca@35: |top slv edt a vvp| ca@35: ca@35: a := Array new:5. ca@35: a at:4 put:(Array new:6). ca@35: ca@35: top := StandardSystemView new extent:600@400. ca@35: vvp := VariableVerticalPanel origin:0.0@0.0 corner:1.0@1.0 in:top. ca@35: cg@2621: slv := Tools::NewInspectorPanelView origin:0.0@0.0 corner:1.0@0.5 in:vvp. ca@35: edt := Workspace origin:0.0 @ 0.5 corner:1.0 @ 1.0 in:vvp. ca@35: edt acceptAction:[:theText|slv accept:theText notifying:edt]. ca@35: edt doItAction:[:theCode|slv doIt:theCode notifying:edt]. ca@35: ca@35: slv action:[:el| Transcript showCR:(el printString)]. ca@35: slv inspect:a. ca@35: ca@35: top open. cg@2621: [exEnd] ca@35: " ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView class methodsFor:'constants'! ca@35: ca@35: minDepth ca@39: "returns the minimum of views assigned to a panel ca@35: " ca@35: ^ 4 ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'accessing'! ca@35: ca@35: depth ca@35: "returns number of listViews ca@35: " ca@35: ^ listViews size ca@35: ! ca@35: ca@35: depth:aDepth ca@35: "change the number of existing listViews ca@35: " ca@35: |sz min| ca@35: ca@35: min := self class minDepth. ca@35: ca@35: aDepth > min ifTrue:[ cg@2621: sz := aDepth min:maxDepth. ca@35: cg@2621: sz < listViews size ifTrue:[ cg@2621: sz := listViews size cg@2621: ] ca@35: ] ifFalse:[ cg@2621: sz := min ca@35: ]. ca@35: ca@35: listViews size == sz ifTrue:[ cg@2621: sz == aDepth ifFalse:[self moveContentsLeft:1]. ca@35: ] ifFalse:[ cg@2621: [self createViewWithoutRedraw. listViews size ~~ sz] whileTrue. cg@2621: self computeExtentOfFrames. ca@35: cg@2621: (self topView shown) ifTrue:[ cg@2621: hzpView sizeChanged:nil. cg@2621: hzpView realizeAllSubViews. cg@2621: ] ca@35: ] ca@35: ! ca@35: ca@35: maxDepth ca@35: ^ maxDepth ca@35: ! ca@35: ca@35: maxDepth:aNumber ca@35: "change max depth for instance ca@35: " ca@35: aNumber > listViews size ifTrue:[ cg@2621: aNumber >= (self class minDepth) ifTrue:[ cg@2621: maxDepth := aNumber. ca@35: cg@2621: maxDepth < listViews size ifTrue:[ cg@2621: self depth:maxDepth cg@2621: ] cg@2621: ] ca@35: ] ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'accessing actions'! ca@35: ca@35: action:aOneArgBlock ca@35: "set the single click action block. ca@35: If non-nil, that one is evaluated on single click, passing the ca@35: selected instance as argument ca@35: " ca@35: actionBlock := aOneArgBlock ca@35: ca@35: ca@35: ! ca@35: ca@35: valueChangedAction:aOneArgBlock ca@35: "evaluated if an instnace changed its value; passing ca@35: the instance as argument ca@35: " ca@35: valueChangedAction := aOneArgBlock ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'accessing selections'! ca@35: ca@35: inspectedObject ca@35: "returns the current inspected object ca@35: " ca@39: ^ self findLastValidListWithSelection inspectedObject ca@35: ! ca@35: ca@35: selectedInstanceVar ca@35: "returns the current selected instance var ca@35: " ca@39: ^ self findLastValidListWithSelection selectedInstanceVar ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'actions'! ca@35: ca@35: accept:aText notifying:aView ca@39: "evaluating aText on the last selected instance var. on success the views ca@39: are updated. ca@39: " ca@39: self doItOrAccept:[:aList|aList accept:aText notifying:aView] ca@35: ! ca@35: ca@35: doIt:aCode notifying:aView ca@39: "evaluating aCode on the selected instance var; on success the views ca@39: are updated. ca@39: " ca@39: ^ self doItOrAccept:[:aList|aList doIt:aCode notifying:aView] ca@35: ! ca@35: ca@35: inspect:anObject ca@39: "change the inspected object and all views ca@35: " ca@35: |view| ca@35: ca@35: view := listViews first. ca@35: leftHistory removeAll. ca@35: rightHistory removeAll. ca@35: ca@35: view inspect:anObject. ca@35: listViews from:2 do:[:v|v inspect:nil]. ca@35: self update. ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'event handling'! ca@35: ca@35: handlesKeyPress:key inView:someView ca@39: "all keys are handled by this instance itself ca@39: " ca@35: ^ true ca@35: ca@35: ! ca@35: ca@35: keyPress:key x:x y:y view:someView ca@39: "handle some special keys ca@39: " ca@35: key == #CursorLeft ifTrue:[^ self moveContentsRight:1]. ca@35: key == #CursorRight ifTrue:[^ self moveContentsLeft:1 ]. ca@35: ca@35: someView keyPress:key x:x y:y. ca@35: ca@35: ! ca@35: ca@35: singleClickAt:anIndex ca@39: "the view at an index changed its selection caused by a single click ca@35: " ca@35: |view start sivar| ca@35: ca@35: rightHistory removeAll. ca@35: ca@35: view := listViews at:anIndex. ca@35: start := anIndex + 1. ca@35: sivar := view selectedInstanceVar. ca@35: ca@35: start > listViews size ifTrue:[ cg@2621: start >= maxDepth ifTrue:[ cg@2621: self moveContentsLeft:1. cg@2621: ^ actionBlock value:sivar. cg@2621: ]. ca@35: ]. ca@35: ca@35: (view selectedInstanceType) == #directory ifTrue:[ cg@2621: (listViews at:start) setSelection:nil. cg@2621: (listViews at:start) inspect:sivar. cg@2621: cg@2621: start := start + 1. ca@35: ]. ca@35: ca@35: listViews from:start do:[:v|v inspect:nil]. ca@35: self update. ca@35: actionBlock value:sivar. ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'initializing'! ca@35: ca@35: initialize ca@35: "initialize instance ca@35: " ca@35: super initialize. ca@35: ca@35: frames := OrderedCollection new. ca@35: listViews := OrderedCollection new. ca@35: labelViews := OrderedCollection new. ca@35: leftHistory := OrderedCollection new. ca@35: rightHistory := OrderedCollection new. ca@35: maxDepth := self class minDepth. ca@35: ca@35: actionBlock := [:el| ]. ca@35: ca@35: hzpView := VariableHorizontalPanel origin:0.0@0.0 corner:1.0@1.0 in:self. ca@35: scrollBar := HorizontalScrollBar origin:0.0@1.0 corner:1.0@1.0 in:self. cg@2299: "/ scrollBar asynchronousOperation. ca@35: ca@35: hzpView bottomInset:(scrollBar preferredExtent y). ca@35: ca@35: scrollBar topInset:(scrollBar preferredExtent y) negated. ca@35: scrollBar thumbHeight:100. ca@35: scrollBar scrollAction:[:percent | self scrollTo:percent]. ca@35: scrollBar scrollRightAction:[self moveContentsLeft:1]. ca@35: scrollBar scrollLeftAction:[self moveContentsRight:1]. ca@35: ca@35: self depth:maxDepth. ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'menu - labels & actions'! ca@35: ca@35: browse:anIndex ca@35: self classAtLabel:anIndex do:[:cls| cls browserClass openInClass:cls selector:nil ] ca@35: ca@35: ! ca@35: ca@35: browseClassHierarchy:anIndex ca@35: self classAtLabel:anIndex do:[:cls| cls browserClass browseClassHierarchy:cls ] ca@35: ca@35: ! ca@35: ca@35: browseFullClassProtocol:anIndex ca@35: self classAtLabel:anIndex do:[:cls| cls browserClass browseFullClassProtocol:cls ] ca@35: ca@35: ! ca@35: ca@35: classAtLabel:anIndex do:anAction ca@35: "evaluate action on class assigned to label ca@35: " ca@35: |cls| ca@35: ca@35: anIndex <= labelViews size ifTrue:[ cg@2621: (cls := Smalltalk classNamed:((labelViews at:anIndex) label)) notNil ifTrue:[ cg@2621: anAction value:cls cg@2621: ] ca@35: ] ca@35: ca@35: ! ca@35: ca@35: labelMenu ca@35: "popup menu required by any label. Delegate the request to the corresponding label ca@35: " ca@35: |sqNr view| ca@35: sv@2171: view := (WindowGroup lastEventQuerySignal query) view. ca@35: sqNr := labelViews findFirst:[:v| v == view]. ca@35: ca@35: sqNr ~~ 0 ifTrue:[ cg@2621: view := labelViews at:sqNr. ca@35: cg@2621: view label notEmpty ifTrue:[ cg@2621: ^ self labelMenu:sqNr cg@2621: ] ca@35: ]. ca@35: ^ nil ca@35: ! ca@35: ca@35: labelMenu:anIndex ca@35: "popup menu required for a label identified by its sequence number ca@35: " ca@35: |menu| ca@35: ca@35: menu := PopUpMenu labels:#( cg@2621: 'browse' cg@2621: 'browse class hierarchy' cg@2621: 'browse full class protocol' cg@2621: ) cg@2621: selectors:#( cg@2621: browse: cg@2621: browseClassHierarchy: cg@2621: browseFullClassProtocol: cg@2621: ) cg@2621: receiver:self. ca@35: ca@35: menu args:(Array new:(menu labels size) withAll:anIndex). ca@35: ^ menu ca@35: ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'menu - views & actions'! ca@35: ca@35: doTrace:anInstance ca@35: "place a trace on messages sent to the instance ca@35: " ca@35: |selectors| ca@35: ca@35: selectors := self messageMenu:anInstance. ca@35: ca@35: selectors notNil ifTrue:[ cg@2621: self topView withWaitCursorDo:[MessageTracer trace:anInstance selectors:selectors] ca@35: ]. ca@35: ca@35: ! ca@35: ca@35: doTraceAll:anInstance ca@35: "place a trace on all messages sent to the instance ca@35: " ca@35: self topView withWaitCursorDo:[MessageTracer traceAll:anInstance] ca@35: ! ca@35: ca@35: doTrap:anInstance ca@35: "place a trap on a message sent to the instance ca@35: " ca@35: |selectors| ca@35: ca@35: selectors := self messageMenu:anInstance. ca@35: ca@35: selectors notNil ifTrue:[ cg@2621: self topView withWaitCursorDo:[MessageTracer trap:anInstance selectors:selectors] ca@35: ] ca@35: ! ca@35: ca@35: doTrapAll:anInstance ca@35: "place a trap on all messages sent to the instance ca@35: " ca@35: self topView withWaitCursorDo:[MessageTracer trapAll:anInstance] ca@35: ca@35: ! ca@35: ca@35: doUntrace:anInstance ca@35: "remove all traps and traces to the instance ca@35: " ca@35: self topView withWaitCursorDo:[MessageTracer untrace:anInstance]. ca@35: ca@35: ! ca@35: ca@35: messageMenu:anInstance ca@35: "open menu to select messages; on accepted a list of messages is returned ca@35: " ca@35: |sll acl lst inset top hzp slv acv dblClcAct btp b1 b2 accepted viewSpacing| ca@35: ca@35: top := StandardSystemView new. ca@35: top extent:500 @ 400. ca@35: top label:(anInstance printString). ca@35: ca@35: (Label origin:(0.0 @ 0.0) corner:(0.5 @ 20) in:top) label:'messages'. ca@35: (Label origin:(0.5 @ 0.0) corner:(1.0 @ 20) in:top) label:'selected'. ca@35: hzp := VariableHorizontalPanel origin:(0.0 @ 20) corner:(1.0 @ 1.0) in:top. ca@35: btp := HorizontalPanelView origin:(0.0 @1.0) corner:(1.0 @ 1.0) in:top. ca@35: ca@35: b1 := Button abortButtonIn:btp. ca@35: b2 := Button okButtonIn:btp. ca@35: accepted := false. ca@35: ca@35: b1 action:[accepted := false. top destroy]. ca@35: b2 action:[accepted := true. top destroy]. ca@35: ca@35: btp horizontalLayout:#fitSpace. ca@35: viewSpacing := top class viewSpacing. ca@35: inset := (b2 preferredExtent y) + viewSpacing. ca@35: viewSpacing := viewSpacing // 2. ca@35: ca@35: hzp bottomInset:inset. ca@35: btp topInset:((inset - viewSpacing) negated). ca@35: btp bottomInset:viewSpacing. ca@35: ca@35: slv := ScrollableView for:SelectionInListView cg@2621: miniScrollerV:true cg@2621: origin:(0.0 @ 0.0) cg@2621: corner:(0.5 @ 1.0) cg@2621: in:hzp. ca@35: ca@35: acv := ScrollableView for:SelectionInListView cg@2621: miniScrollerV:true cg@2621: origin:(0.5 @ 0.0) cg@2621: corner:(1.0 @ 1.0) cg@2621: in:hzp. ca@35: ca@35: slv := slv scrolledView. ca@35: acv := acv scrolledView. ca@35: ca@35: sll := (MessageTracer realClassOf:anInstance) selectors. ca@35: acl := OrderedCollection new. ca@35: ca@35: (MessageTracer wrappedSelectorsOf:anInstance) do:[:el| cg@2621: el notNil ifTrue:[ cg@2621: acl add:el. cg@2621: sll remove:el ifAbsent:nil cg@2621: ] ca@35: ]. cg@2621: ca@35: slv list:(sll copy). ca@35: acv list:(acl copy). ca@35: ca@35: dblClcAct := [:from :to| cg@2621: to add:(from selectionValue). cg@2621: from removeIndex:(from selection). cg@2621: from redraw. ca@35: ]. ca@35: ca@35: slv doubleClickAction:[:index| dblClcAct value:slv value:acv]. ca@35: acv doubleClickAction:[:index| dblClcAct value:acv value:slv]. ca@35: ca@35: top openModal. ca@35: ca@35: accepted ifFalse:[ cg@2621: ^ nil ca@35: ]. ca@35: lst := acv list. ca@35: ca@35: "undo existing traps HACK: removes traps and traces" ca@35: ca@35: acl notEmpty ifTrue:[ cg@2621: MessageTracer untrace:anInstance ca@35: ]. ca@35: ca@35: lst notEmpty ifTrue:[^ lst] cg@2621: ifFalse:[^ nil] ca@35: ! ca@35: ca@35: viewMenu ca@35: "popup menu required by any view. Delegate the request to the corresponding view ca@35: " ca@35: |sqNr view| ca@35: sv@2171: view := (WindowGroup lastEventQuerySignal query) view. ca@35: sqNr := listViews findFirst:[:v| v == view]. ca@35: ca@35: sqNr notNil ifTrue:[^ self viewMenu:sqNr] cg@2621: ifFalse:[^ nil] ca@35: ! ca@35: ca@35: viewMenu:anIndex ca@35: "popup menu required for a view identified by its sequence number ca@35: " cg@327: |view menu inst args lbls| ca@35: ca@35: view := listViews at:anIndex. ca@35: view hasSelection ifFalse:[^ nil]. ca@35: inst := view selectedInstanceVar. ca@35: ca@39: menu := PopUpMenu labels:#( 'update' ) cg@2621: selectors:#( #update ) cg@2621: receiver:self. ca@35: ca@35: menu actionAt:#update put:[ cg@2621: view update. ca@35: cg@2621: listViews from:(anIndex + 1) do:[:v| cg@2621: (view selectedInstanceType) ~~ #directory ifTrue:[ cg@2621: v inspect:nil cg@2621: ] ifFalse:[ cg@2621: v inspect:(view selectedInstanceVar). cg@2621: view := v. cg@2621: ] cg@2621: ]. cg@2621: self update ca@35: ]. ca@35: cg@1213: (NewInspectorList isTraceable:inst) ifFalse:[ cg@2621: ^ menu ca@39: ]. ca@39: ca@35: menu addLabels:#( cg@2621: '-' cg@2621: 'trace' cg@2621: 'trap' cg@2621: 'untrace / untrap' cg@2621: ) cg@2621: selectors:#( cg@2621: nil cg@2621: trace cg@2621: trap cg@2621: untrace cg@2621: ). ca@35: ca@35: menu actionAt:#untrace put:[self doUntrace:inst]. ca@35: ca@35: args := Array new:2 withAll:inst. ca@35: lbls := Array with:'message' cg@2621: with:((Text string:' all ' emphasis:#underline), ' messages'). ca@35: ca@35: menu subMenuAt:#trace put:( cg@2621: PopUpMenu labels:lbls selectors:#(doTrace: doTraceAll:) args:args ca@35: ). ca@35: ca@35: menu subMenuAt:#trap put:( cg@2621: PopUpMenu labels:lbls selectors:#(doTrap: doTrapAll:) args:args ca@35: ). ca@35: ca@35: ^ menu ca@35: ca@35: ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'private'! ca@35: ca@35: doItOrAccept:aBlock ca@39: "handle a doIt or accept action; on success all the folloed views are ca@39: updated ca@35: " ca@39: |index list result instVar| ca@35: ca@39: list := self findLastValidListWithSelection. ca@39: result := aBlock value:list. ca@39: instVar := list selectedInstanceVar. ca@39: index := listViews findLast:[:v|v == list]. ca@35: ca@39: (index ~~ 0 and:[index ~~ listViews size]) ifTrue:[ cg@2621: index := index + 1. cg@2621: (list selectedInstanceType) == #directory ifTrue:[ cg@2621: (listViews at:index) inspect:instVar cg@2621: ] ifFalse:[ cg@2621: (listViews at:index) inspect:nil cg@2621: ]. cg@2621: self update ca@39: ]. ca@39: valueChangedAction notNil ifTrue:[ cg@2621: valueChangedAction value:instVar ca@35: ]. ca@39: ^ result ca@39: ! ca@39: ca@39: findLastValidListWithSelection ca@39: "returns last valid list with a selection; if no selection exists in any ca@39: view, the list assigned to the inspected object is returned ca@39: " ca@39: |index| ca@39: ca@39: rightHistory notEmpty ifTrue:[ cg@2621: ^ rightHistory first ca@39: ]. ca@39: index := listViews findLast:[:v| v hasSelection ]. ca@35: ca@35: index ~~ 0 ifTrue:[ cg@2621: ^ listViews at:index ca@39: ]. ca@35: ca@39: leftHistory notEmpty ifTrue:[^ leftHistory last] cg@2621: ifFalse:[^ listViews at:1] ca@35: ! ca@35: ca@35: update ca@35: "update labels and scrollbar ca@35: " ca@35: |pview cview stop index ispObj label| ca@35: ca@35: "UPDATE LABELS ca@35: " ca@35: index := 1. ca@35: stop := listViews size. ca@35: ca@35: [ cview := listViews at:index. cg@2621: ispObj := cview inspectedObject. cg@2621: label := labelViews at:index. cg@2621: index := index + 1. ca@35: cg@2621: ispObj notNil ifTrue:[ cg@2621: label label:(ispObj class name asString). cg@2621: pview := cview. cg@2621: ] ifFalse:[ cg@2621: [index <= stop] whileTrue:[ cg@2621: (labelViews at:index) label:''. cg@2621: index := index + 1 cg@2621: ]. ca@35: cg@2621: (pview isNil or:[pview selectedInstanceType == #normal]) ifTrue:[ cg@2621: pview notNil ifTrue:[ispObj := pview selectedInstanceVar]. cg@2621: label label:ispObj class name asString cg@2621: ] ifFalse:[ cg@2621: label label:'' cg@2621: ] cg@2621: ]. cg@2621: index > stop ca@35: ca@35: ] whileFalse. ca@35: ca@35: "UPDATE SCROLLBARS ca@35: " ca@35: index := listViews size + leftHistory size + rightHistory size. ca@35: ca@35: (listViews last) selectedInstanceType notNil ifTrue:[ cg@2621: index := index + 1 ca@35: ]. ca@35: scrollBar thumbHeight:(stop / index) * 100. ca@35: scrollBar thumbOrigin:(100 / index * leftHistory size). ca@35: ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'private frames'! ca@35: ca@35: computeExtentOfFrames ca@35: "compute the extent of all frames (origin/corner) ca@35: " ca@35: |orig corn offset newX| ca@35: ca@35: orig := ( 0.0 @ 0.0 ). ca@35: corn := ( 0.0 @ 1.0 ). ca@35: ca@35: offset := 1.0 / (frames size). ca@35: newX := 0.0. ca@35: ca@35: frames do:[:frame| cg@2621: (newX := newX + offset) > 1.0 ifTrue:[ newX := 1.0 ]. cg@2621: corn := newX @ corn y. cg@2621: frame origin:orig corner:corn. cg@2621: orig := newX @ orig y. ca@35: ]. ca@35: ca@35: ca@35: ! ca@35: ca@35: createViewWithoutRedraw ca@39: "add a new view at end of the panel ca@35: " ca@35: |view frame label index| ca@35: ca@35: frame := SimpleView in:hzpView. ca@35: ca@35: label := Label origin:0.0@0.0 corner:1.0@20 in:frame. ca@35: label leftInset:15. ca@35: label rightInset:2. ca@35: cg@2621: view := ScrollableView for:NewInspectorListView miniScroller:true origin:0.0@20 cg@2621: corner:1.0@1.0 in:frame. ca@35: ca@35: view := view scrolledView. ca@35: ca@35: frames add:frame. ca@35: labelViews add:label. ca@35: listViews add:view. ca@35: ca@35: index := listViews size. ca@35: ca@35: index == 1 ifTrue:[ cg@2621: view includesSelf:true ca@35: ]. ca@35: ca@35: label adjust:#left. ca@35: label label:''. ca@35: label level:1. ca@35: label menuHolder:self; menuMessage:#labelMenu; menuPerformer:self. ca@35: ca@35: view action:[:el|self singleClickAt:index]. ca@35: ca@35: view delegate:self. ca@35: view menuHolder:self; menuMessage:#viewMenu; menuPerformer:self. ca@35: ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView methodsFor:'scrolling-basic'! ca@35: ca@35: moveContentsLeft:nTimes ca@39: "move the contents of all views one position left ca@35: " cg@327: |fView stop pView index| ca@35: ca@35: (nTimes < 1 or:[listViews last isEmpty]) ifTrue:[ cg@2621: ^ self ca@35: ]. ca@35: ca@35: index := nTimes. ca@35: stop := (listViews size) - 1. ca@35: fView := listViews first. ca@35: pView := listViews at:stop. ca@35: ca@35: ca@39: [ leftHistory add:(fView list). ca@35: cg@2621: 1 to:stop do:[:i| cg@2621: (listViews at:i) list:(listViews at:(i+1)) cg@2621: ]. ca@35: cg@2621: rightHistory notEmpty ifTrue:[ cg@2621: (listViews last) list:(rightHistory removeLast) cg@2621: ] ifFalse:[ cg@2621: (listViews last) inspect:(pView selectedInstanceVar) cg@2621: ]. cg@2621: ((index := index - 1) == 0 or:[listViews last isEmpty]) ca@35: ca@35: ] whileFalse. ca@35: ca@35: self update. ca@35: ca@35: ca@35: ca@35: ! ca@35: ca@35: moveContentsRight:nTimes ca@39: "move the contents of all views one position right ca@35: " cg@327: |size index lView fView| ca@35: ca@35: size := leftHistory size. ca@35: ca@35: (nTimes > 0 and:[size ~~ 0]) ifTrue:[ cg@2621: nTimes > size ifFalse:[index := nTimes] cg@2621: ifTrue:[index := size]. ca@35: cg@2621: size := listViews size. cg@2621: lView := listViews last. cg@2621: fView := listViews first. ca@35: cg@2621: 1 to:index do:[:i| cg@2621: lView hasSelection ifTrue:[ cg@2621: rightHistory add:(lView list) cg@2621: ]. cg@2621: size to:2 by:-1 do:[:i| cg@2621: (listViews at:i) list:(listViews at:(i-1)) cg@2621: ]. cg@2621: fView list:(leftHistory removeLast) cg@2621: ]. cg@2621: self update ca@35: ] ca@35: ca@35: ! ca@35: ca@35: scrollTo:nPercent ca@39: "set views and contents dependant on scroll bar ca@35: " ca@35: |dY no noScr pR| ca@35: ca@35: noScr := listViews size + leftHistory size + rightHistory size. ca@35: ca@35: (listViews last) selectedInstanceType notNil ifTrue:[ cg@2621: noScr := noScr + 1 ca@35: ]. ca@35: dY := 100 / noScr. ca@35: pR := nPercent roundTo:dY. ca@35: ca@35: no := ((dY * leftHistory size) - pR) / dY. ca@35: ca@35: no == 0 ifTrue:[ cg@2621: (nPercent - pR) > 0 ifTrue:[no := -1] cg@2621: ifFalse:[no := 1] ca@35: ]. ca@35: no < 0 ifTrue:[self moveContentsLeft:(no negated)] cg@2621: ifFalse:[self moveContentsRight:no] ca@35: ! ! ca@35: cg@1213: !NewInspectorPanelView class methodsFor:'documentation'! ca@35: ca@35: version ca@35: ^ '$Header$' ca@35: ! !