isResizeable
authorca
Tue, 24 Jun 1997 16:14:11 +0200
changeset 175 0b0b4d99e3e7
parent 174 0e87610c2768
child 176 a9e5b1615761
isResizeable
UIObjectView.st
UIPainterView.st
--- a/UIObjectView.st	Mon Jun 23 12:53:14 1997 +0200
+++ b/UIObjectView.st	Tue Jun 24 16:14:11 1997 +0200
@@ -14,8 +14,8 @@
 
 ObjectView subclass:#UIObjectView
 	instanceVariableNames:'saveSelection inputView enableChannel undoHistory copiedExtent
-		copiedLayout actionData createClass clipChildren
-		selectionHiddenLevel setOfSuperViewsSizeChanged'
+		copiedLayout resizeData clipChildren selectionHiddenLevel
+		setOfSuperViewsSizeChanged'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-UIPainter'
@@ -167,8 +167,97 @@
 
 ! !
 
+!UIObjectView class methodsFor:'handles'!
+
+handlesOf:aView do:aBlock
+    |type v h|
+
+    type := self layoutType:aView.
+
+    (type == #LayoutFrame or:[type == #Rectangle]) ifTrue:[
+        v := self isVerticalResizable:aView.
+        h := self isHorizontalResizable:aView.
+
+        h ifTrue:[  aBlock value:(aView leftCenter ) value:#left.
+                    aBlock value:(aView rightCenter) value:#right.
+                 ].
+        v ifTrue:[  aBlock value:(aView topCenter   ) value:#top.
+                    aBlock value:(aView bottomCenter) value:#bottom.
+                 ].
+
+        (h and:[v]) ifTrue:[
+            aBlock value:(aView origin    ) value:#origin.
+            aBlock value:(aView topRight  ) value:#topRight.
+            aBlock value:(aView bottomLeft) value:#bottomLeft.
+            aBlock value:(aView corner    ) value:#corner.
+          ^ self
+        ]
+    ].
+
+    aBlock value:(aView origin    ) value:#view.
+    aBlock value:(aView topRight  ) value:#view.
+    aBlock value:(aView bottomLeft) value:#view.
+
+    type == #Extent ifTrue:[
+        v := self isVerticalResizable:aView.
+        h := self isHorizontalResizable:aView.
+
+        v ifTrue:[aBlock value:(aView bottomCenter) value:#bottom].
+        h ifTrue:[aBlock value:(aView rightCenter ) value:#right ].
+
+        (h and:[v]) ifTrue:[
+            aBlock value:(aView corner) value:#corner.
+          ^ self
+        ]
+    ].
+    aBlock value:(aView corner) value:#view.
+
+
+! !
+
 !UIObjectView class methodsFor:'queries'!
 
+isHorizontalResizable:aComponent
+    "returns true if instance is horizontal resizeable
+    "
+    (aComponent isKindOf:ScrollBar) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    (aComponent isKindOf:Scroller) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    (aComponent isKindOf:Slider) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    ^ true
+
+!
+
+isVerticalResizable:aComponent
+    "returns true if instance is vertical resizeable
+    "
+    (aComponent isKindOf:EditField) ifTrue:[
+        ^ false
+    ].
+    (aComponent isKindOf:ComboBoxView) ifTrue:[
+        ^ false
+    ].
+    (aComponent isKindOf:CheckBox) ifTrue:[
+        ^ false
+    ].
+    (aComponent isKindOf:ScrollBar) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    (aComponent isKindOf:Scroller) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    (aComponent isKindOf:Slider) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    ^ true
+
+!
+
 layoutType:aView
     "returns layout type of aView or nil
     "
@@ -329,6 +418,11 @@
     "
     self halt
 
+!
+
+startCreate:aPoint
+    self setDefaultActions.
+    self halt
 ! !
 
 !UIObjectView methodsFor:'event handling'!
@@ -347,24 +441,21 @@
 exposeX:x y:y width:w height:h
     "handle an expose event from device; redraw selection
     "
-    super exposeX:x y:y width:w height:h.
-
-"
-catch expose events for all subviews associated with
-a selected instance
-"
-
-    "/ handle any expose events (for subcomponents) before
-    "/ redrawing the handles.
-    (self sensor hasExposeEventFor:nil) ifTrue:[^ self].
-
-    self selectionDo:[:aComponent |
-        aComponent withAllSubViewsDo:[:v |
-            self sensor flushExposeEventsFor:v.
-            v exposeX:0 y:0 width:9999 height:9999.
-        ].
-
-        self showSelected:aComponent
+    resizeData isNil ifTrue:[
+        super exposeX:x y:y width:w height:h.
+
+        "/ handle any expose events (for subcomponents) before
+        "/ redrawing the handles.
+        (self sensor hasExposeEventFor:nil) ifTrue:[^ self].
+
+        self selectionDo:[:aComponent |
+            aComponent withAllSubViewsDo:[:v |
+                self sensor flushExposeEventsFor:v.
+                v exposeX:0 y:0 width:9999 height:9999.
+            ].
+
+            self showSelected:aComponent
+        ]
     ]
 
 !
@@ -455,27 +546,29 @@
 
 !
 
-invertOutlineOf:anObject
-    "invert outline of an object
+invertOutlineOf:something
+    "invert outline of an object or collection of objects
     "
-    |wasClipped delta|
+    |wasClipped p|
 
     (wasClipped := clipChildren) ifTrue:[
         self clippedByChildren:(clipChildren := false).
     ].
-    delta := (anObject originRelativeTo:self) - anObject origin.
-
-    self xoring:[
-        self displayRectangle:((anObject origin + delta) extent:anObject extent).
+
+    something isCollection ifTrue:[
+        something do:[:v|
+            p := v originRelativeTo:self.
+            self xoring:[self displayRectangle:(p extent:v extent)].
+        ]
+    ] ifFalse:[
+        p := something originRelativeTo:self.
+        self xoring:[self displayRectangle:(p extent:something extent)]
     ].
 
     wasClipped ifTrue:[
         self clippedByChildren:(clipChildren := true).
     ].
 
-    "Modified: 5.9.1995 / 12:25:25 / claus"
-
-
 !
 
 minSetOfSuperViews:setOfViews
@@ -502,177 +595,18 @@
 
 ! !
 
-!UIObjectView methodsFor:'object creation'!
-
-actionCreate:anObject frame:aFrame delta:aDelta
-    "create and initialize action data
-    "
-    |extent x y selectors values|
-
-"minimum extent
-"
-    (anObject specClass supportsSubComponents) ifTrue:[
-        extent := 25@25
-    ] ifFalse:[
-        extent := self extent.
-        x := extent x // 3.
-        y := extent y // 3.
-        extent := anObject preferredExtent.
-
-        (extent x > x) ifTrue:[extent x:x].
-        (extent y > y) ifTrue:[extent y:y].
-    ].
-
-"setup structure
-"
-    selectors := #( object frame delta vertical horizontal minExtent ).
-    values    := Array new:(selectors size).
-
-    values at:1 put:anObject.
-    values at:2 put:aFrame.
-    values at:3 put:aDelta.
-    values at:4 put:(self isVerticalResizable:anObject).
-    values at:5 put:(self isHorizontalResizable:anObject).
-    values at:6 put:extent.
-
-    actionData := Structure newWith:selectors values:values.
-
-
-"can change cursor dependent on vertical/horizontal resizing
-"
-    oldCursor := cursor.
-    self cursor:(Cursor leftHand).
-
-
-
-!
-
-createWidgetWithClass:aClass
-    "prepare to create new widgets
-    "
-    aClass notNil ifTrue:[
-        createClass := aClass.
-        pressAction := [:aPoint| self startCreate:aPoint].
-        self cursor:Cursor origin.
-    ]
-
-!
-
-doDragCreate:aPoint
-    "do a widget create drag
-    "
-    |frame object extent minimum|
-
-    frame   := actionData frame.
-    frame corner:((self alignToGrid:aPoint) - (actionData delta)).
-
-    object  := actionData object.
-    minimum := actionData minExtent.
-    extent  := frame extent.
-
-    ((extent x < minimum x) or:[actionData horizontal not]) ifTrue:[
-        extent x:(minimum x)
-    ].
-
-    ((extent y < minimum y) or:[actionData vertical not]) ifTrue:[
-        extent y:(minimum y)
-    ].
-
-    frame extent:extent.
-
-    self invertOutlineOf:object.
-    object origin:(frame origin) extent:(frame extent).
-    self invertOutlineOf:object.
-!
-
-endCreate
-    "end a widget create drag
-    "
-    |object specClass|
-
-    object := actionData object.
-    self invertOutlineOf:object.
-    inputView raise.
-
-    self setupInitialLayoutFor:object.
-    self select:object.
-    actionData := nil.
-
-    self setDefaultActions.
-
-!
-
-initializeCreatedObject:anObject
-    self subclassResponsibility
-!
-
-setupInitialLayoutFor:anObject
-    "setup initial layout for an object; !!!! some kludge !!!!
-    "
-    |spec topSpec|
-
-    topSpec := anObject superView specClass basicNew.
-
-    topSpec class isLayoutContainer ifFalse:[
-
-"/ ... KLUDGE ....
-
-        spec := anObject specClass.
-
-        (    spec == ViewSpec
-         or:[spec == SubCanvasSpec
-         or:[spec == TextEditorSpec
-         or:[spec == SequenceViewSpec]]]
-        ) ifTrue:[
-            anObject geometryLayout:(anObject bounds asLayout).
-          ^ self
-        ]
-    ].
-    topSpec setupInitialLayoutFor:anObject.
-
-!
-
-startCreate:aPoint
-    "start a widget create
-    "
-    |widget object start frame delta|
-
-    self select:nil.
-    widget := self findContainerViewAt:aPoint.
-
-    motionAction  := [:movePoint| self doDragCreate:movePoint].
-    releaseAction := [ self endCreate].
-
-    object := createClass new.
-    (widget isKindOf:ScrollableView) ifTrue:[
-        widget scrolledView:object
-    ] ifFalse:[
-        widget addSubView:object.
-    ].
-
-    start := self alignToGrid:aPoint.
-    delta := widget originRelativeTo:self.
-    frame := Rectangle origin:(start - delta) corner:start.
-
-    object origin:(frame origin).
-    self initializeCreatedObject:object.
-    self actionCreate:object frame:frame delta:delta.
-    object extent:(actionData minExtent).
-    object realize.
-    self invertOutlineOf:object.
-! !
-
 !UIObjectView methodsFor:'object moving'!
 
 doObjectMove:aPoint
     "move selection
     "
     movedObject notNil ifTrue:[
-        movedObject keysAndValuesDo:[:nr :aView|
-            self invertOutlineOf:aView.
-            self moveObject:aView to:(aPoint - (moveDelta at:nr)).
-            self invertOutlineOf:aView.
-        ]
+        self invertOutlineOf:movedObject.
+
+        movedObject keysAndValuesDo:[:i :v|
+            self moveObject:v to:(aPoint - (moveDelta at:i)).
+        ].
+        self invertOutlineOf:movedObject.
     ]
 
 !
@@ -681,12 +615,11 @@
     "cleanup after object(s) move
     "
     movedObject notNil ifTrue:[
-        movedObject do:[:aView|self invertOutlineOf:aView].
+        self invertOutlineOf:movedObject.
 
         movedObject size == 1 ifTrue:[
             movedObject := movedObject first
         ].
-
         self setSelection:movedObject withRedraw:true.
         movedObject := nil.
         self setDefaultActions.
@@ -728,12 +661,8 @@
     moveDelta := movedObject collect:[:aView|
         aPoint - aView computeOrigin
     ].
-
-    self transaction:#move objects:movedObject do:[:aView|
-        self invertOutlineOf:aView.
-        self createUndoLayout:aView
-    ].
-
+    self transaction:#move objects:movedObject do:[:v|self createUndoLayout:v].
+    self invertOutlineOf:movedObject.
 !
 
 startSelectMoreOrMove:aPoint
@@ -819,7 +748,7 @@
     delta    := anObject container originRelativeTo:self.
     selector := ('resize:', aSelector, ':') asSymbol.
 
-    actionData := Structure with:(#object->anObject)
+    resizeData := Structure with:(#object->anObject)
                             with:(#selector->selector)
                             with:(#delta->delta).
 
@@ -837,12 +766,12 @@
     "
     |p object|
 
-    object := actionData object.
+    object := resizeData object.
 
     self invertOutlineOf:object.
-    p := (self alignToGrid:aPoint) - (actionData delta).
-
-    self perform:(actionData selector) with:object with:p.
+    p := (self alignToGrid:aPoint) - (resizeData delta).
+
+    self perform:(resizeData selector) with:object with:p.
    "/ object geometryLayout:(object geometryLayout).
     self invertOutlineOf:object
 
@@ -853,8 +782,8 @@
     "
     |object|
 
-    object := actionData object.
-    actionData := nil.
+    object := resizeData object.
+    resizeData := nil.
 
     self invertOutlineOf:object.
     self setDefaultActions.
@@ -891,73 +820,41 @@
 
 !UIObjectView methodsFor:'private handles'!
 
-handlesOf:aView do:aBlock
-    |dlta type v h|
-
-    dlta := (aView originRelativeTo:self) - aView origin.
-    type := self class layoutType:aView.
-
-    (type == #LayoutFrame or:[type == #Rectangle]) ifTrue:[
-        v := self isVerticalResizable:aView.
-        h := self isHorizontalResizable:aView.
-
-        h ifTrue:[  aBlock value:(aView leftCenter   + dlta) value:#left.
-                    aBlock value:(aView rightCenter  + dlta) value:#right.
-                 ].
-        v ifTrue:[  aBlock value:(aView topCenter    + dlta) value:#top.
-                    aBlock value:(aView bottomCenter + dlta) value:#bottom.
-                 ].
-
-        (h and:[v]) ifTrue:[
-            aBlock value:(aView origin     + dlta) value:#origin.
-            aBlock value:(aView topRight   + dlta) value:#topRight.
-            aBlock value:(aView bottomLeft + dlta) value:#bottomLeft.
-            aBlock value:(aView corner     + dlta) value:#corner.
-          ^ self
-        ]
-    ].
-
-    aBlock value:(aView origin     + dlta) value:#view.
-    aBlock value:(aView topRight   + dlta) value:#view.
-    aBlock value:(aView bottomLeft + dlta) value:#view.
-
-    type == #Extent ifTrue:[
-        v := self isVerticalResizable:aView.
-        h := self isHorizontalResizable:aView.
-
-        v ifTrue:[aBlock value:(aView bottomCenter + dlta) value:#bottom].
-        h ifTrue:[aBlock value:(aView rightCenter  + dlta) value:#right ].
-
-        (h and:[v]) ifTrue:[
-            aBlock value:(aView corner + dlta) value:#corner.
-          ^ self
-        ]
-    ].
-    aBlock value:(aView corner + dlta) value:#view.
+handlesOf:aComponent do:aTwoArgAction
+    "perform action on each handle of a component
+    "
+    |dlt ext|
+
+    dlt := (aComponent originRelativeTo:self) - aComponent origin.
+    dlt := dlt - (3@3).
+    ext := 6@6.
+
+    self class handlesOf:aComponent do:[:pnt :wht |
+        aTwoArgAction value:(pnt + dlt extent:ext) value:wht
+    ]
 !
 
 showSelected:aComponent
     "show object selected
     "
-    |wasClipped delta|
-
-    selectionHiddenLevel ~~ 0 ifTrue:[^ self].
-
-    self paint:Color black.
-
-    (wasClipped := clipChildren) ifTrue:[
-        self clippedByChildren:(clipChildren := false). 
-    ].
-
-    self handlesOf:aComponent do:[:pnt :what |
-        what == #view ifTrue:[self displayRectangle:(pnt - (4@4) extent:7@7)]
-                     ifFalse:[self    fillRectangle:(pnt - (4@4) extent:7@7)]
-    ].
-
-    wasClipped ifTrue:[
-        self clippedByChildren:(clipChildren := true).
-    ].
-
+    |wasClipped|
+
+    selectionHiddenLevel == 0 ifTrue:[
+        self paint:Color black.
+
+        (wasClipped := clipChildren) ifTrue:[
+            self clippedByChildren:(clipChildren := false). 
+        ].
+
+        self handlesOf:aComponent do:[:rectangle :what|
+            what == #view ifTrue:[self displayRectangle:rectangle]
+                         ifFalse:[self fillRectangle:rectangle]
+        ].
+
+        wasClipped ifTrue:[
+            self clippedByChildren:(clipChildren := true).
+        ]
+    ]
 !
 
 showUnselected:aComponent
@@ -971,9 +868,7 @@
         self clippedByChildren:(clipChildren := false). 
     ].
 
-    self handlesOf:aComponent do:[:pnt :what |
-        self clearRectangle:(pnt - (4@4) extent:7@7).
-    ].
+    self handlesOf:aComponent do:[:rec :wht| self clearRectangle:rec ].
 
     wasClipped ifTrue:[
         self clippedByChildren:(clipChildren := true). 
@@ -981,8 +876,7 @@
 
     "/ must redraw all components which are affected b the handles
 
-    r := (aComponent originRelativeTo:self) - (4@4)
-             extent:(aComponent extent + (4@4)).
+    r := (aComponent originRelativeTo:self) - (3@3) extent:(aComponent extent + (6@6)).
 
     subViews do:[:anotherComponent |
         |absOrg absFrame|
@@ -1004,21 +898,13 @@
     "Modified: 8.4.1997 / 00:32:26 / cg"
 !
 
-whichHandleOf:aView isHitBy:aPoint
+whichHandleOf:aComponent isHitBy:aPoint
     "returns kind of handle or nil
     "
-    |bounds|
-
-    self handlesOf:aView do:[:pnt :what |
-        ((pnt - (4@4) extent:7@7) containsPoint:aPoint) ifTrue:[
-            ^ what
-        ].
+    self handlesOf:aComponent do:[:rectangle :what|
+        (rectangle containsPoint:aPoint) ifTrue:[^ what]
     ].
-
-    ^ nil
-
-    "Modified: 5.9.1995 / 14:39:34 / claus"
-
+  ^ nil
 ! !
 
 !UIObjectView methodsFor:'private resizing-subviews'!
@@ -1219,48 +1105,6 @@
     ^ nil
 
 
-!
-
-isPoint:aPoint containedIn:aView
-    "checks whether a point is covered by a view.
-    "
-    |p|
-
-    p := device translatePoint:aPoint from:inputView id to:aView id.
-
-    (p x >= 0 and:[p y >= 0]) ifTrue:[
-        p := aView extent - p.
-
-        (p x >= 0 and:[p y >= 0]) ifTrue:[
-            ^ true
-        ]
-    ].
-    ^ false
-!
-
-whichBorderOf:aView isHitBy:aPoint
-    |p r bw org|
-
-    bw := aView borderWidth.
-    p := aPoint - (aView superView originRelativeTo:self).
-
-    r := Rectangle origin:(aView origin)
-                   extent:(aView width @ bw).
-    (r containsPoint:p) ifTrue:[^ #top:].
-
-    r origin:(aView left @ (aView bottom + bw)) extent:(aView width @ bw).
-    (r containsPoint:p) ifTrue:[^ #bottom:].
-
-    r top:(aView top).
-    r extent:(bw @ aView height).
-    (r containsPoint:p) ifTrue:[^ #left:].
-
-    r origin:((aView right + bw) @ aView top).
-    (r containsPoint:p) ifTrue:[^ #right:].
-
-    ^ nil
-
-
 ! !
 
 !UIObjectView methodsFor:'selections'!
@@ -1533,14 +1377,6 @@
 
 !
 
-isHorizontalResizable:aComponent
-    "returns true if instance is horizontal resizeable
-    "
-    ^ self subclassResponsibility
-
-
-!
-
 isModified
     "returns true if painter is modified
     "
@@ -1555,22 +1391,6 @@
     ].
   ^ false
 
-!
-
-isVerticalResizable:aComponent
-    "returns true if instance is vertical resizeable
-    "
-    ^ self subclassResponsibility
-
-
-!
-
-supportsLabel:aComponent
-    "returns true if component supports label
-    "
-    ^ self subclassResponsibility
-
-
 ! !
 
 !UIObjectView methodsFor:'transaction'!
--- a/UIPainterView.st	Mon Jun 23 12:53:14 1997 +0200
+++ b/UIPainterView.st	Tue Jun 24 16:14:11 1997 +0200
@@ -17,16 +17,16 @@
 	category:'Interface-UIPainter'
 !
 
-Object subclass:#ViewProperty
-	instanceVariableNames:'view spec identifier'
-	classVariableNames:'Identifier'
+MultiSelectionInList subclass:#ListHolder
+	instanceVariableNames:'painter propertyList masterElement disabledChanged'
+	classVariableNames:''
 	poolDictionaries:''
 	privateIn:UIPainterView
 !
 
-MultiSelectionInList subclass:#ListHolder
-	instanceVariableNames:'painter propertyList masterElement disabledChanged'
-	classVariableNames:''
+Object subclass:#ViewProperty
+	instanceVariableNames:'view spec identifier'
+	classVariableNames:'Identifier'
 	poolDictionaries:''
 	privateIn:UIPainterView
 !
@@ -578,10 +578,7 @@
         |modelSelector menuSelector protoSpec thisCode|
 
         protoSpec := aProp spec.
-        protoSpec isNil ifTrue:[
-            self halt.
-            protoSpec := aProp view specClass basicNew.
-        ].
+
         (modelSelector := aProp model) notNil ifTrue:[
             (cls implements:modelSelector asSymbol) ifFalse:[
                 skip := false.
@@ -602,7 +599,6 @@
 
         (menuSelector := aProp menu) notNil ifTrue:[
             (cls implements:menuSelector asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateAspectMethodFor:menuSelector spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
@@ -610,14 +606,12 @@
 
         aProp spec aspectSelectors do:[:aSel|
             (cls implements:aSel asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateAspectMethodFor:aSel spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
         ].
         aProp spec actionSelectors do:[:aSel|
             (cls implements:aSel asSymbol) ifFalse:[
-                "/ kludge ..
                 thisCode := (self generateActionMethodFor:aSel spec:protoSpec inClass:cls).
                 code := code , thisCode
             ]
@@ -625,151 +619,6 @@
 
     ].
     ^ code
-
-    "Modified: 17.6.1997 / 14:07:36 / cg"
-!
-
-generateClassDefinition
-    |defCode|
-
-    defCode := superclassName , ' subclass:#' , className , '\'.
-    defCode := defCode , '  instanceVariableNames:'''.
-    defCode := defCode , self subviewVariableNames , '''\'.
-    defCode := defCode , '  classVariableNames:''''\'.
-    defCode := defCode , '  poolDictionaries:''''\'.
-    defCode := defCode , '  category:''' , categoryName , '''\'.
-    defCode := defCode , Character excla asString , '\\'.
-
-    ^ defCode withCRs
-
-
-
-!
-
-generateCode
-    "generate code for the windowSpec method"
-
-    |code|
-
-    self resetModification.
-
-    code := ''.
-
-"/    (Smalltalk classNamed:className asSymbol) isNil ifTrue:[
-"/        code := code , self generateClassDefinition.
-"/    ].
-"/    code := code , self generateInitMethod.
-
-    code := code , self generateWindowSpecMethodSource.
-
-"/    code := code , self generateAspectMethods.
-
-    ^ code withCRs
-
-    "Modified: 5.9.1995 / 20:57:53 / claus"
-!
-
-generateInitCodeForView:aView
-    |code c name p outlets moreCode sym typ val|
-
-    " <name> := <ViewClass> in:<name-of-superview>"
-
-    code := ''.
-
-    p := self propertyOfView:aView.
-    name := p at:#variableName.
-    c := '    ' , name , ' := ' ,
-         (aView class name) , ' in:' , (self uniqueNameOf:(aView superView)) , '.\'.
-
-    " <name> origin:(...) extent:(...)"
-
-    c := c , '    ' , name , ' origin:(', aView origin printString , ')'
-                    , ' extent:(', aView extent printString , ').\'.
-
-    moreCode := p at:#initCode ifAbsent:nil.
-    moreCode notNil ifTrue:[
-        c := c , moreCode , '\' withCRs
-    ].
-
-    code := code , c withCRs.
-
-    " <name> <symbol>:<value>"
-
-    outlets := p at:#outlets ifAbsent:[nil].
-    outlets notNil ifTrue:[
-        outlets do:[:selectorOutlet |
-            sym := selectorOutlet at:#selector.
-            typ := selectorOutlet at:#type.
-            val := selectorOutlet at:#value.
-            c :=  '    ' , name , ' ' , sym.
-            (typ == #number) ifTrue:[
-                c := c , val printString
-            ].
-            (typ == #string) ifTrue:[
-                c := c , '''' , val , ''''
-            ].
-            (typ == #text) ifTrue:[
-                c := c , '''' , val asString , ''''
-            ].
-            (typ == #strings) ifTrue:[
-                c := c , '#( '.
-                val asText do:[:aString |
-                    c := c , '''' , aString , ''' '
-                ].
-                c := c , ')'
-            ].
-            (typ == #block) ifTrue:[
-                c := c , val
-            ].
-            (typ == #color) ifTrue:[
-                c := c , '(Color name:''' , val , ''')'
-            ].
-            c := c , '.' , Character cr asString.
-            code := code , c
-        ]
-    ].
-
-    self subviewsOf:aView do:[:v |
-        code := code , (self generateInitCodeForView:v)
-    ].
-    ^ code.
-
-    "Modified: 5.9.1995 / 20:06:07 / claus"
-!
-
-generateInitMethod
-    |defCode code|
-
-    defCode := Character excla asString ,
-               className , ' methodsFor:''initialization''' ,
-               Character excla asString , '\\'.
-
-    defCode := defCode , 'initialize\'.
-    defCode := defCode , '    super initialize.\'.
-    defCode := defCode , '    self setupSubViews.\'.
-    defCode := defCode , '    self setupLocalStuff\'.
-    defCode := defCode , Character excla asString , '\\'.
-
-    defCode := defCode , 'setupSubViews\'.
-    code := defCode withCRs.
-
-    self subviewsOf:self do:[:v |
-        code := code , (self generateInitCodeForView:v)
-    ].
-    code := code , '    ^ self\' withCRs.
-
-    defCode := Character excla asString , '\\'.
-    defCode := defCode , 'setupLocalStuff\'.
-    defCode := defCode , '    ^ self\'.
-    defCode := defCode , Character excla asString , ' ' ,
-                         Character excla asString , '\\'.
-
-    code := code , defCode withCRs.
-    ^ code.
-
-
-
-
 !
 
 generateWindowSpecMethodSource
@@ -819,27 +668,6 @@
     ^ code withCRs
 
     "Modified: 5.9.1995 / 21:01:35 / claus"
-!
-
-storeContentsOn:aStream
-    listHolder propertiesDo:[:p| p storeOn:aStream]
-!
-
-subviewsOf:aView do:aBlock
-    |subs v|
-
-    (subs := aView subViews) notNil ifTrue:[
-        subs do:[:v|
-            (v ~~ inputView and:[v notNil]) ifTrue:[
-                (listHolder detectProperty:[:p|p view == v]) notNil ifTrue:[ 
-                    (v superView == aView) ifTrue:[
-                        aBlock value:v
-                    ]
-                ]
-            ]
-        ]
-    ]
-
 ! !
 
 !UIPainterView methodsFor:'initialization'!
@@ -867,29 +695,6 @@
 
 !
 
-initializeCreatedObject:anObject
-    "set default properties for a created object
-    "
-    |props spec cls|
-
-    cls   := anObject class.
-    spec  := anObject specClass fromView:anObject.
-    props := ViewProperty new.
-    props view:anObject.
-    props spec:spec.
-    props name:(self uniqueNameFor:spec).
-    listHolder add:props.
-
-    ((spec respondsTo:#label:) and:[self supportsLabel:anObject]) ifTrue:[
-        anObject label:(props name).
-        spec label:(props name)
-    ].
-
-    undoHistory withinTransaction:#create text:(props name) do:[
-        undoHistory addUndoSelector:#undoCreate: withArgs:(props identifier)
-    ].
-!
-
 setupFromSpec:specOrSpecArray
     |spec builder|
 
@@ -1079,49 +884,6 @@
 
 ! !
 
-!UIPainterView methodsFor:'selection'!
-
-addTreeFrom:aView to:aCollection
-    "add aView and contained subcomponents to collection
-    "
-    (self propertyOfView:aView) notNil ifTrue:[
-        aCollection add:aView.
-
-        (aView subViews notNil) ifTrue:[
-            aView subViews do:[:subView|
-                self addTreeFrom:subView to:aCollection
-            ]
-        ].
-    ]
-
-!
-
-selectSubComponents
-    "select all subcomponents for current selection
-    "
-    |startAtView aCollection|
-
-    aCollection := OrderedCollection new.
-    startAtView := self singleSelection.
-
-    startAtView isNil ifTrue:[
-        self subViews notNil ifTrue:[
-            self subViews do:[:subView|
-                subView ~~ inputView ifTrue:[
-                    self addTreeFrom:subView to:aCollection
-                ]
-            ]
-        ]
-    ] ifFalse:[
-        self addTreeFrom:startAtView to:aCollection
-    ].
-
-    aCollection size > 1 ifTrue:[
-        self updateSelectionFrom:aCollection.
-        self selectionChanged
-    ]
-! !
-
 !UIPainterView methodsFor:'specification'!
 
 addSpec:aSpecification builder:aBuilder in:aFrame
@@ -1245,64 +1007,6 @@
     ]
 ! !
 
-!UIPainterView methodsFor:'testing'!
-
-isHorizontalResizable:aComponent
-    "returns true if instance is horizontal resizeable
-    "
-    (aComponent isKindOf:ScrollBar) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    (aComponent isKindOf:Scroller) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    (aComponent isKindOf:Slider) ifTrue:[
-        ^ aComponent orientation == #horizontal
-    ].
-    ^ true
-
-
-!
-
-isVerticalResizable:aComponent
-    "returns true if instance is vertical resizeable
-    "
-    (aComponent isKindOf:EditField) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:ComboBoxView) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:CheckBox) ifTrue:[
-        ^ false
-    ].
-    (aComponent isKindOf:ScrollBar) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    (aComponent isKindOf:Scroller) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    (aComponent isKindOf:Slider) ifTrue:[
-        ^ aComponent orientation == #vertical
-    ].
-    ^ true
-
-
-!
-
-supportsLabel:aComponent
-    "returns true if component supports label
-    "
-    (aComponent respondsTo:#label:) ifTrue:[
-        (    (aComponent isKindOf:ArrowButton) 
-          or:[aComponent isKindOf:CheckToggle]
-        ) ifFalse:[
-            ^ true
-        ]
-    ].
-    ^ false
-! !
-
 !UIPainterView methodsFor:'transaction'!
 
 transaction:aType objects:something do:aOneArgBlock
@@ -1459,105 +1163,6 @@
 
 ! !
 
-!UIPainterView::ViewProperty class methodsFor:'documentation'!
-
-version
-    ^ '$Header$'
-! !
-
-!UIPainterView::ViewProperty class methodsFor:'instance creation'!
-
-new
-    Identifier notNil ifTrue:[Identifier := Identifier + 1]
-                     ifFalse:[Identifier := 1].
-
-  ^ self basicNew initialize
-! !
-
-!UIPainterView::ViewProperty methodsFor:'accessing'!
-
-identifier
-    "return the unique identifier assigned to property
-    "
-    ^ identifier
-!
-
-identifier:anIdentifier
-    "set the unique identifier assigned to property; called after an restore of
-     a deleted instance
-    "
-    identifier := anIdentifier
-!
-
-spec
-    "return the value of the instance variable 'spec' (automatically generated)"
-
-    ^ spec!
-
-spec:something
-    "set the value of the instance variable 'spec' (automatically generated)"
-
-    spec := something.!
-
-view
-    "return the value of the instance variable 'view' (automatically generated)"
-
-    ^ view!
-
-view:something
-    "set the value of the instance variable 'view' (automatically generated)"
-
-    view := something.! !
-
-!UIPainterView::ViewProperty methodsFor:'initialization'!
-
-initialize
-    super initialize.
-    identifier := Identifier
-! !
-
-!UIPainterView::ViewProperty methodsFor:'misc'!
-
-extractNumberStartingAt:anIndex
-    "return the number from the name starting at anIndex or 0.
-    "
-    |val|
-
-    val := 0.
-
-    self name from:anIndex do:[:c|
-        c isDigit ifTrue:[val := val * 10 + c digitValue]
-                 ifFalse:[^ 0]
-    ].
-    ^ val
-        
-! !
-
-!UIPainterView::ViewProperty methodsFor:'spec messages'!
-
-doesNotUnderstand:aMessage
-    spec notNil ifTrue:[
-        (spec respondsTo:(aMessage selector)) ifTrue:[^ aMessage sendTo:spec]
-    ].
-    ^ nil
-!
-
-layout
-    spec layout
-!
-
-layout:aLayout
-    spec layout:aLayout
-!
-
-name
-    ^ spec name
-!
-
-name:aName
-    spec name:aName
-! !
-
 !UIPainterView::ListHolder class methodsFor:'instance creation'!
 
 for:aPainter
@@ -1891,6 +1496,105 @@
     super selectionIndex:aSel
 ! !
 
+!UIPainterView::ViewProperty class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+
+!UIPainterView::ViewProperty class methodsFor:'instance creation'!
+
+new
+    Identifier notNil ifTrue:[Identifier := Identifier + 1]
+                     ifFalse:[Identifier := 1].
+
+  ^ self basicNew initialize
+! !
+
+!UIPainterView::ViewProperty methodsFor:'accessing'!
+
+identifier
+    "return the unique identifier assigned to property
+    "
+    ^ identifier
+!
+
+identifier:anIdentifier
+    "set the unique identifier assigned to property; called after an restore of
+     a deleted instance
+    "
+    identifier := anIdentifier
+!
+
+spec
+    "return the value of the instance variable 'spec' (automatically generated)"
+
+    ^ spec!
+
+spec:something
+    "set the value of the instance variable 'spec' (automatically generated)"
+
+    spec := something.!
+
+view
+    "return the value of the instance variable 'view' (automatically generated)"
+
+    ^ view!
+
+view:something
+    "set the value of the instance variable 'view' (automatically generated)"
+
+    view := something.! !
+
+!UIPainterView::ViewProperty methodsFor:'initialization'!
+
+initialize
+    super initialize.
+    identifier := Identifier
+! !
+
+!UIPainterView::ViewProperty methodsFor:'misc'!
+
+extractNumberStartingAt:anIndex
+    "return the number from the name starting at anIndex or 0.
+    "
+    |val|
+
+    val := 0.
+
+    self name from:anIndex do:[:c|
+        c isDigit ifTrue:[val := val * 10 + c digitValue]
+                 ifFalse:[^ 0]
+    ].
+    ^ val
+        
+! !
+
+!UIPainterView::ViewProperty methodsFor:'spec messages'!
+
+doesNotUnderstand:aMessage
+    spec notNil ifTrue:[
+        (spec respondsTo:(aMessage selector)) ifTrue:[^ aMessage sendTo:spec]
+    ].
+    ^ nil
+!
+
+layout
+    spec layout
+!
+
+layout:aLayout
+    spec layout:aLayout
+!
+
+name
+    ^ spec name
+!
+
+name:aName
+    spec name:aName
+! !
+
 !UIPainterView class methodsFor:'documentation'!
 
 version