UIPainterTreeView.st
changeset 49 7f58dd5fc836
parent 43 3dd91a85c243
child 54 d0b5a33e6df0
--- a/UIPainterTreeView.st	Fri Feb 14 18:20:05 1997 +0100
+++ b/UIPainterTreeView.st	Sat Feb 15 19:14:01 1997 +0100
@@ -10,8 +10,8 @@
  hereby transferred.
 "
 
-ObjectView subclass:#UIPainterTreeView
-	instanceVariableNames:'builderView indent yPos maxX'
+SelectionInListView subclass:#UIPainterTreeView
+	instanceVariableNames:'builderView'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-UIPainter'
@@ -39,134 +39,85 @@
 "
 ! !
 
-!UIPainterTreeView class methodsFor:'startup'!
+!UIPainterTreeView class methodsFor:'constants'!
 
-start
-    |topView v|
+indent
+    "indent for contained element
+    "
+    ^ 2
+
 
-    topView := StandardSystemView 
-		    label:'View hierarchy'
-		    icon:(Form fromFile:'BuildTreeV.icon' resolution:100).
-    v  := HVScrollableView for:self in:topView.
-    v origin:(0 @ 0) extent:(1.0 @ 1.0).
+! !
+
+!UIPainterTreeView class methodsFor:'defaults'!
 
-    topView realize.
-    ^ v scrolledView
-
-    "BuilderTreeView start"
+defaultMenuMessage   
+    "This message is the default yo be sent to the menuHolder to get a menu
+    "
+    ^ #editMenu
 
 
 ! !
 
-!UIPainterTreeView methodsFor:'BuilderView interface'!
+!UIPainterTreeView methodsFor:'accessing'!
 
 builderView:aBuilderView
     builderView := aBuilderView.
-
+    self updateTree.
 
 !
 
-selectName:aString
-    contents do:[:obj |
-        (obj text asString withoutSeparators = aString) ifTrue:[
-            ^ self select:obj.
-        ]
-   ]
+indexOf:aString
+    "returns the index of the string entry into my list
+    "
+    ^ list findFirst:[:aName| aName withoutSeparators = aString ]
+
+
+! !
+
+!UIPainterTreeView methodsFor:'event handling'!
 
-!
+selectionChanged
+    "selection has changed
+    "
+    |sel|
 
-selectNameAdd:aString
-    contents do:[:obj |
-        (obj text asString withoutSeparators = aString) ifTrue:[
-            ^ self addToSelection:obj.
+    selection notNil ifTrue:[
+        selection size == 1 ifTrue:[
+            sel := (list at:(selection first)) withoutSeparators
+        ] ifFalse:[
+            sel := OrderedCollection new.
+            selection do:[:aNumber|
+                aNumber ~~ 1 ifTrue:[
+                    sel add:((list at:aNumber) withoutSeparators)
+                ]
+            ]
         ]
-   ]
-
+    ].
+    builderView selectName:sel
 
 !
 
 update:something
-    |sel|
 
-    something == #tree ifTrue:[
-        ^ self updateTree.
-    ].
-
-    something == #widgetName ifTrue:[
+    (something == #tree or:[something == #widgetName]) ifTrue:[
         self updateTree
     ] ifFalse:[
         something == #selection ifFalse:[
             ^ self
-        ]
+        ].
+        self setSelection:nil.
     ].
 
-    sel := builderView selection.
-
-    (sel isKindOf:Collection) ifTrue:[
-        sel do:[:v | self selectNameAdd:(builderView variableNameOf:v)]
-    ] ifFalse:[
-        self selectName:(builderView variableNameOf:sel)
-    ]
-
-! !
-
-!UIPainterTreeView methodsFor:'drawing'!
-
-showSelected:anObject
-    "show an object as selected"
-
-    |oldFg oldBg|
-
-    oldFg := anObject foreground.
-    oldBg := anObject background.
-    anObject foreground:oldBg.
-    anObject background:oldFg.
-    anObject drawIn:self.
-    anObject foreground:oldFg.
-    anObject background:oldBg
-
-    "Modified: 31.8.1995 / 13:52:02 / claus"
-! !
-
-!UIPainterTreeView methodsFor:'generating the class-tree picture'!
-
-addToTree:name indent:indent
-    |newObject|
+    "update selection
+    "
+    builderView selectionDo:[:aView||idx|
+        idx := self indexOf:(builderView variableNameOf:aView).
 
-    newObject := DrawText new.
-    "newObject font:font.  "
-    newObject text:name.
-    newObject origin:((indent asInteger + margin) @ yPos).
-    newObject foreground:Color black. "/ foreground.
-    newObject background:Color white. "/background.
-    newObject linePattern:1; fillPattern:1. "/ opaque
-    yPos := yPos + newObject frame height.
-    self add:newObject.
-    maxX := maxX max:(newObject frame corner x).
-
-    "Modified: 5.9.1995 / 23:54:26 / claus"
-!
-
-addViewsToTreeFrom:aView indent:currentIndent
-    |name|
-
-    name := builderView variableNameOf:aView.
-    self addToTree:name indent:currentIndent.
-
-    builderView subviewsOf:aView do:[:subview |
-        self addViewsToTreeFrom:subview
-                           indent:(currentIndent + indent)
+        idx ~~ 0 ifTrue:[
+            self addToSelection:idx
+        ]
     ]
-!
-
-updateTree
-    self removeAll.
-    maxX := 0.
-    yPos := (self verticalPixelPerMillimeter:1) rounded asInteger.
-    self addViewsToTreeFrom:builderView indent:(self horizontalPixelPerMillimeter:1).
-    self contentsChanged
-
-    "Modified: 5.9.1995 / 23:54:35 / claus"
 ! !
 
 !UIPainterTreeView methodsFor:'initialization'!
@@ -174,79 +125,29 @@
 initialize
     super initialize.
 
-    maxX := 0.
-    yPos := (self verticalPixelPerMillimeter:1) rounded asInteger.
-    indent := (self horizontalPixelPerMillimeter:5) rounded asInteger.
-    sorted := true.
-    pressAction := [:aPoint | self click:aPoint].
-    shiftPressAction := [:aPoint | self shiftClick:aPoint]
-
-    "Modified: 6.9.1995 / 00:11:48 / claus"
-!
-
-initializeMiddleButtonMenu
-    |labels|
+    list := OrderedCollection new.
 
-    labels := resources array:#(
-                        'inspect view'
-                        'inspect properties'
-                       ).
+    self multipleSelectOk:true.
+    self action:[:aSelection| self selectionChanged ].
 
-    self middleButtonMenu:(PopUpMenu
-                                labels:labels
-                             selectors:#(
-                                         inspectView
-                                         inspectProps
-                                        )
-                                receiver:self
-                                     for:self)
+
 ! !
 
-!UIPainterTreeView methodsFor:'private'!
-
-selectedName
-    selection isNil ifTrue:[^ nil].
-    ^ selection text asString withoutSeparators
-!
-
-withSelectedNameDo:aBlock
-    |name|
+!UIPainterTreeView methodsFor:'menu & actions'!
 
-    name := self selectedName.
-    name notNil ifTrue:[aBlock value:name]
-! !
-
-!UIPainterTreeView methodsFor:'queries'!
-
-heightOfContents
-    ^ yPos  + (self verticalPixelPerMillimeter:1) rounded
-
-    "Modified: 6.9.1995 / 12:56:24 / claus"
-!
+editMenu
+    |menu ispMenu|
 
-widthOfContents
-    ^ maxX + (self horizontalPixelPerMillimeter:1) rounded
-
-    "Modified: 6.9.1995 / 12:56:28 / claus"
-! !
-
-!UIPainterTreeView methodsFor:'user interaction'!
-
-click:aPoint
-    |anObject|
+    menu := PopUpMenu labels:#( 'inspect' )
+                   selectors:#( #inspect  )
+                    receiver:self.
 
-    anObject := self findObjectAtVisible:aPoint.
-    (anObject ~~ selection) ifTrue:[
-        self unselect.
-        anObject notNil ifTrue:[
-            self select:anObject.
-            builderView selectName:(self selectedName)
-        ] ifFalse:[
-            builderView selectName:'self'
-        ]
-    ]
+    ispMenu := PopUpMenu labels:#( 'view'        'property'     )
+                      selectors:#( #inspectView  #inspectProps  )
+                       receiver:self.
 
-
+    menu subMenuAt:#inspect put:ispMenu.
+  ^ menu
 
 
 !
@@ -257,25 +158,35 @@
 
 inspectView
     builderView inspectSelection
-!
+! !
+
+!UIPainterTreeView methodsFor:'update'!
 
-shiftClick:aPoint
-    |anObject|
+updateSubTree:aView indent:anIndent
+    |name indent|
 
-    anObject := self findObjectAtVisible:aPoint.
+    name := builderView variableNameOf:aView.
 
-    anObject notNil ifTrue:[
-        (self isSelected:anObject) ifTrue:[
-            builderView removeNameFromSelection:anObject text asString withoutSeparators
-        ] ifFalse:[
-            builderView addNameToSelection:anObject text asString withoutSeparators
-        ]
+    anIndent ~~ 0 ifTrue:[
+        name := (String new:anIndent), name
+    ].
+    list add:name.
+
+    indent := anIndent + self class indent.
+
+    builderView subviewsOf:aView do:[:subview|
+        self updateSubTree:subview indent:indent
     ]
 
 
+!
 
+updateTree
 
-
+    selection := nil.
+    list      := OrderedCollection new.
+    self updateSubTree:builderView indent:0.
+    super list:list.
 
 ! !