*** empty log message ***
authorca
Sat, 15 Feb 1997 19:19:32 +0100
changeset 51 01d0c9394944
parent 50 fb4359c9bdc4
child 52 40a98a1507b4
*** empty log message ***
UIObjectView.st
UIPainterView.st
--- a/UIObjectView.st	Sat Feb 15 19:15:25 1997 +0100
+++ b/UIObjectView.st	Sat Feb 15 19:19:32 1997 +0100
@@ -1,15 +1,1559 @@
+ObjectView subclass:#UIObjectView
+        instanceVariableNames:'inputView testMode undoHistory copiedExtent resizedObject
+                resizeSelector createInWidget createFrame createdObject
+                createClass clipChildren'
+        classVariableNames:''
+        poolDictionaries:''
+        category:'Interface-UIPainter'
+!
+
 Object subclass:#UndoHistory
-	instanceVariableNames:'history transaction enabled modifiedAction'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UIObjectView
+        instanceVariableNames:'history transaction enabled modifiedAction'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UIObjectView
+!
+
+
+!UIObjectView class methodsFor:'defaults'!
+
+defaultGrid
+    ^ 4 @ 4
+
+!
+
+gridShown
+    ^ false
+
+!
+
+handleSize
+    "size of blob drawn for handles"
+    ^ 4
+
+!
+
+hitDelta
+    ^ 4
+
+! !
+
+!UIObjectView methodsFor:'accessing'!
+
+gridParameters
+    "used by defineGrid, and in a separate method for
+     easier redefinition in subclasses. 
+     Returns the grid parameters in an array of 7 elements,
+     which control the appearance of the grid-pattern.
+     the elements are:
+
+        bigStepH        number of pixels horizontally between 2 major steps
+        bigStepV        number of pixels vertically between 2 major steps
+        littleStepH     number of pixels horizontally between 2 minor steps
+        littleStepV     number of pixels vertically between 2 minor steps
+        gridAlignH      number of pixels for horizontal grid align (pointer snap)
+        gridAlignV      number of pixels for vertical grid align (pointer snap)
+        docBounds       true, if document boundary should be shown
+
+     if littleStepH/V are nil, only bigSteps are drawn.
+    "
+
+    ^ #(10 10 nil nil 10 10 false)
+
+
+!
+
+hideGrid
+    gridShown ifTrue:[
+        self withSelectionHiddenDo:[
+            super hideGrid
+        ]
+    ]
+
+
+!
+
+showGrid
+    self withSelectionHiddenDo:[
+        super showGrid
+    ]
+
+    "Modified: 5.9.1995 / 12:47:46 / claus"
+
+
+!
+
+testMode
+    "returns testMode
+    "
+    ^ testMode
+
+
+!
+
+testMode:aBoolean
+    "change testMode
+    "
+    (aBoolean == testMode) ifFalse:[
+        testMode := aBoolean.
+
+        testMode ifTrue:[
+            self unselect.
+            inputView unrealize
+        ] ifFalse:[
+            inputView raise.
+            inputView realize
+        ]
+    ]
+
+
+! !
+
+!UIObjectView methodsFor:'event handling'!
+
+doKeyInput:key
+    ^ self
+
+
+!
+
+elementChanged:aView 
+    "some element has been changed - kludge to force a resizing
+     operation (for child layout recomputation) in its superView"
+
+    aView superView sizeChanged:nil.
+    self changed:#any.
+
+
+!
+
+elementChangedLayout:aView 
+    "some element has been changed - kludge to force a resizing
+     operation (for child layout recomputation) in its superView"
+
+    aView superView sizeChanged:nil.
+    self changed:#layout.
+
+
+!
+
+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.
+
+    selection notNil ifTrue:[
+        self selectionDo:[:v | self showSelected:v]
+    ]
+
+
+!
+
+keyPress:key x:x y:y
+
+    key == #InspectIt ifTrue:[
+        ^ self inspectSelection
+    ].
+
+    (key == #Delete or:[key == #BackSpace]) ifTrue: [
+        selection notNil ifTrue:[
+            self deleteSelection
+        ]
+    ] ifFalse:[
+        keyPressAction notNil ifTrue:[
+            keyPressAction value:key
+        ]
+    ]
+
+
+!
+
+processEvent:anEvent
+    "catch expose events for components, and redraw its handles after
+     the redraw when this happens
+    "
+    |view|
+
+    selection notNil ifTrue:[
+        anEvent type == #damage ifTrue:[
+            view := anEvent view.
+            (selection == view
+            or:[selection isCollection
+                and:[selection includes:view]]) ifTrue:[
+                    self showSelected:view
+            ]
+        ]
+    ].
+    ^ false.
+
+
+!
+
+sizeChanged:how
+    self withSelectionHiddenDo:[
+        super sizeChanged:how
+    ]
+
+
+! !
+
+!UIObjectView methodsFor:'initialization'!
+
+initialize
+    super initialize.
+
+    "funny: since I do not want the created widgets to get pointer
+     events, I put an InputView on top of them, which catches those events
+     and passes them back to me - have to take care, that this inputView
+     is always on top
+    "
+    inputView := InputView origin:0.0@0.0 extent:1.0@1.0 in:self.
+
+    inputView eventReceiver:self.
+    inputView enableButtonEvents.
+    inputView enableButtonMotionEvents.
+
+    self setDefaultActions.
+
+    undoHistory := UndoHistory new.
+
+    undoHistory modifiedAction:[:what|
+        self changed:#undoHistory with:what
+    ].
+
+    testMode := false.
+    clipChildren := true.
+
+    (self class gridShown) ifTrue:[
+        super showGrid
+    ].
+
+!
+
+realize
+    super realize.
+    self windowGroup postEventHook:self
+
+! !
+
+!UIObjectView methodsFor:'misc'!
+
+cursor:aCursor
+    inputView realized ifTrue:[
+        inputView cursor:aCursor
+    ].
+    super cursor:aCursor
+
+
+!
+
+invertOutlineOf:anObject
+    |wasClipped delta|
+
+    (wasClipped := clipChildren) ifTrue:[
+        self clippedByChildren:(clipChildren := false).
+    ].
+    delta := (anObject originRelativeTo:self) - anObject origin.
+
+    self xoring:[
+        self displayRectangle:((anObject origin + delta) extent:anObject extent).
+    ].
+
+    wasClipped ifTrue:[
+        self clippedByChildren:(clipChildren := true).
+    ].
+
+    "Modified: 5.9.1995 / 12:25:25 / claus"
+
+
+!
+
+setDefaultActions
+
+    pressAction      := [:pressPoint | self startSelectOrMove:pressPoint].
+    shiftPressAction := [:pressPoint | self startSelectMoreOrMove:pressPoint].
+    motionAction     := [:movePoint  | nil].
+    releaseAction    := [nil].
+    keyPressAction   := [:key | self doKeyInput:key].
+
+    self cursor:Cursor normal.
+
+!
+
+showDragging:something offset:anOffset
+    "drag around a View"
+
+    |top|
+
+    self forEach:something do:[:anObject |
+        self drawRectangle:((anObject origin + anOffset) extent:(anObject extent))
+    ]
+
+! !
+
+!UIObjectView methodsFor:'object creation'!
+
+doDragCreate:aPoint
+    "do a widget create drag
+    "
+    |p|
+
+    p := self alignToGrid:aPoint.
+    createFrame corner:(p - (createInWidget originRelativeTo:self)).
+
+    (createFrame extent x < 10) ifTrue:[
+        createFrame extent x:10
+    ].
+
+    (createFrame extent y < 10) ifTrue:[
+        createFrame extent y:10
+    ].
+
+    self invertOutlineOf:createdObject.
+    createdObject origin:(createFrame origin) extent:(createFrame extent).
+    self invertOutlineOf:createdObject.
+!
+
+endCreate
+    "end a widget create drag
+    "
+    |layout x y|
+
+    self invertOutlineOf:createdObject.
+    inputView raise.
+
+    layout := createdObject bounds asLayout.
+    createdObject geometryLayout:layout.
+
+    self changed:#tree.
+    self select:createdObject.
+    createdObject := nil.
+
+    self setDefaultActions.
+
+!
+
+setupCreatedObject:anObject
+    self subclassResponsibility
+!
+
+startCreate:aPoint
+    "start a widget create
+    "
+    |startPoint|
+
+    createClass isNil ifTrue:[
+        ^ self setDefaultActions
+    ].
+    (selection isKindOf:Collection) ifTrue:[
+        self unselect.
+      ^ self setDefaultActions.
+    ].
+
+    startPoint    := self alignToGrid:aPoint.
+    motionAction  := [:movePoint| self doDragCreate:movePoint].
+    releaseAction := [ self endCreate].
+
+    selection notNil ifTrue:[
+        (    (self isPoint:aPoint containedIn:selection)
+         and:[selection specClass basicNew supportsSubComponents]
+        ) ifFalse:[
+            self unselect
+        ]
+    ].
+
+    oldCursor := cursor.
+    self cursor:(Cursor leftHand).
+
+    createInWidget := selection ? self.
+    createdObject  := createClass new.
+    createInWidget addSubView:createdObject.
+
+    createFrame := Rectangle origin:(startPoint - (createInWidget originRelativeTo:self))
+                             corner:startPoint.
+
+    createdObject origin:(createFrame origin).
+
+    undoHistory transactionNamed:'create' do:[
+        self setupCreatedObject:createdObject.
+    ].
+    createdObject realize.
+    self invertOutlineOf:createdObject.
+! !
+
+!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.
+        ]
+    ]
+
+!
+
+endObjectMove
+    "cleanup after object move"
+
+    movedObject notNil ifTrue:[
+        movedObject do:[:aView|
+            self invertOutlineOf:aView
+        ].
+
+        movedObject do:[:aView|
+            self showSelected:aView
+        ].
+        movedObject size == 1 ifTrue:[
+            selection := movedObject at:1
+        ] ifFalse:[
+            selection := movedObject
+        ].
+
+        movedObject := nil.
+        self setDefaultActions.
+        self changed:#layout.
+    ].
+!
+
+startObjectMoveAt:aPoint
+
+    self startObjectMove:selection at:aPoint.
+
+    selection size == 0 ifTrue:[
+        movedObject := Array with:selection
+    ] ifFalse:[
+        movedObject := selection
+    ].
+    super unselect.
+
+    moveDelta := movedObject collect:[:aView|
+        aPoint - aView computeOrigin
+    ].
+
+    undoHistory transactionNamed:'move' do:[
+        movedObject do:[:aView|
+            self invertOutlineOf:aView.
+            self undoBlockPositionChanged:aView
+        ]
+    ]
+!
+
+startSelectMoreOrMove:aPoint
+    "add/remove to/from selection"
+
+    |anObject|
+
+    testMode ifTrue:[^ self].
+
+    anObject := self findObjectAt:aPoint.
+    anObject notNil ifTrue:[
+        (self isSelected:anObject) ifTrue:[
+            self removeFromSelection:anObject
+        ] ifFalse:[
+            self addToSelection:anObject
+        ]
+    ]
+!
+
+startSelectOrMove:aPoint
+    "a button is pressed at a point
+    "
+    |anObject b|
+
+    testMode ifTrue:[^ self].
+
+    "if there is one selection and point hits handle, start a resize
+    "
+    self singleSelection notNil ifTrue:[
+        b := self whichHandleOf:selection isHitBy:aPoint.
+
+        (b notNil and:[b ~~ #view]) ifTrue:[
+            ^ self startResizeBorder:b of:selection at:aPoint.
+        ]
+    ].
+
+    anObject := self findObjectAt:aPoint.
+
+    "nothing is selected
+    "
+    anObject isNil ifTrue:[
+        ^ self unselect
+    ].
+
+    (self isSelected:anObject) ifFalse:[
+        super unselect.
+        self select:anObject.
+    ].
+
+    selection isCollection ifTrue:[
+        releaseAction := [
+            self setDefaultActions.
+            self select:anObject
+        ]
+    ] ifFalse:[
+        releaseAction := [self setDefaultActions]
+    ].
+
+    "prepare move operation for an object
+    "
+    motionAction := [:movePoint|
+        (aPoint dist:movePoint) > 2.0 ifTrue:[
+            self startObjectMoveAt:aPoint
+        ]
+    ].
+! !
+
+!UIObjectView methodsFor:'private handles'!
+
+handlesOf:aComponent do:aBlock
+    |delta layout vertical horizontal|
+
+    layout := aComponent geometryLayout.
+    delta  := (aComponent originRelativeTo:self) - aComponent origin.
+
+    (layout isLayout not or:[layout isLayoutFrame]) ifTrue:[
+        vertical   := self isVerticalResizable:aComponent.
+        horizontal := self isHorizontalResizable:aComponent.
+    ] ifFalse:[
+        vertical   := false.
+        horizontal := false.
+    ].
+
+    horizontal ifTrue:[
+        aBlock value:(aComponent leftCenter   + delta) value:#left.
+        aBlock value:(aComponent rightCenter  + delta) value:#right.
+    ].
+
+    vertical ifTrue:[
+        aBlock value:(aComponent topCenter    + delta) value:#top.
+        aBlock value:(aComponent bottomCenter + delta) value:#bottom.
+    ].
+
+    (horizontal and:[vertical]) ifTrue:[
+        aBlock value:(aComponent origin     + delta) value:#origin.
+        aBlock value:(aComponent corner     + delta) value:#corner.
+        aBlock value:(aComponent topRight   + delta) value:#topRight.
+        aBlock value:(aComponent bottomLeft + delta) value:#bottomLeft.
+    ] ifFalse:[
+        aBlock value:(aComponent origin     + delta) value:#view.
+        aBlock value:(aComponent corner     + delta) value:#view.
+        aBlock value:(aComponent topRight   + delta) value:#view.
+        aBlock value:(aComponent bottomLeft + delta) value:#view.
+    ].
+
+
+!
+
+showSelected:aComponent
+    |wasClipped delta oldPaint|
+
+    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).
+    ].
+    self paint:oldPaint.
+!
+
+showUnselected:aComponent
+    |wasClipped delta r oldPaint|
+
+    r := aComponent origin extent:8@8.
+
+    (wasClipped := clipChildren) ifTrue:[
+        self clippedByChildren:(clipChildren := false). 
+    ].
+
+    self handlesOf:aComponent do:[:pnt :what |
+        self clearRectangle:(pnt - (4@4) extent:7@7).
+    ].
+
+    wasClipped ifTrue:[
+        self clippedByChildren:(clipChildren := true). 
+    ].
+
+    "/ must redraw all components which are affected b the handles
+
+    r := (aComponent originRelativeTo:self) - (4@4)
+             extent:(aComponent extent + (4@4)).
+
+    subViews do:[:anotherComponent |
+        |absOrg absFrame|
+
+        anotherComponent ~~ inputView ifTrue:[
+            absOrg := anotherComponent originRelativeTo:self.
+            absFrame := absOrg extent:(anotherComponent extent).
+            (absFrame intersects:r) ifTrue:[
+                anotherComponent withAllSubViewsDo:[:v |
+                    v clear.
+                    v exposeX:0 y:0 width:9999 height:9999.
+                ]
+            ]
+        ]
+    ]
+
+!
+
+whichHandleOf:aView isHitBy:aPoint
+    |bounds|
+
+    self handlesOf:aView do:[:pnt :what |
+        ((pnt - (4@4) extent:7@7) containsPoint:aPoint) ifTrue:[
+            ^ what
+        ].
+    ].
+
+    ^ #view
+
+    "Modified: 5.9.1995 / 14:39:34 / claus"
+
+! !
+
+!UIObjectView methodsFor:'private resizing-subviews'!
+
+resize:aView bottom:aPoint
+
+    undoHistory disabledTransitionDo:[
+        self shifLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
+    ]
+!
+
+resize:aView corner:aPoint
+    |delta|
+
+    delta := aPoint - aView computeCorner.
+
+    undoHistory disabledTransitionDo:[
+        self shifLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
+    ]
+!
+
+resize:aView left:aPoint
+
+    undoHistory disabledTransitionDo:[
+        self shifLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
+    ]
+
+!
+
+resize:aView right:aPoint
+
+    undoHistory disabledTransitionDo:[
+        self shifLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
+    ]
+!
+
+resize:aView top:aPoint
+
+    undoHistory disabledTransitionDo:[
+        self shifLayout:aView top:((aPoint y) - (aView computeOrigin y)) bottom:0
+    ]
+! !
+
+!UIObjectView methodsFor:'private shift-layout'!
+
+shifLayout:aView left:l right:r
+    "shift layout for a view; in case of an open transaction, the
+     undoAction will be defined
+    "
+    self shifLayout:aView top:0 bottom:0 left:l right:r
+
+!
+
+shifLayout:aView top:t bottom:b
+    "shift layout for a view; in case of an open transaction, the
+     undoAction will be defined
+    "
+    self shifLayout:aView top:t bottom:b left:0 right:0
+
+
+!
+
+shifLayout:aView top:t bottom:b left:l right:r
+    "shift layout for a view; in case of an open transaction, the
+     undoAction will be defined
+    "
+    |layout|
+
+    self undoBlockPositionChanged:aView.
+
+    layout := aView geometryLayout.
+
+    layout leftOffset:(layout leftOffset + l)
+            topOffset:(layout topOffset  + t).
+
+    layout isLayoutFrame ifTrue:[
+        layout bottomOffset:(layout bottomOffset + b).
+        layout  rightOffset:(layout rightOffset  + r).
+    ].
+
+    aView geometryLayout:layout.
+
+
+
+! !
+
+!UIObjectView methodsFor:'private undo-actions'!
+
+undoBlockDimensionChanged:aView
+
+    undoHistory isTransactionOpen ifTrue:[
+        |layout|
+
+        layout := aView geometryLayout copy.
+
+        undoHistory addUndoBlock:[
+            aView geometryLayout:layout.
+            aView superView sizeChanged:nil.
+        ]
+    ]
+
+!
+
+undoBlockPositionChanged:aView
+
+    undoHistory isTransactionOpen ifTrue:[
+        |layout|
+
+        layout := aView geometryLayout copy.
+        undoHistory addUndoBlock:[aView geometryLayout:layout]
+    ]
+
+! !
+
+!UIObjectView methodsFor:'searching'!
+
+findObjectAt:aPoint
+    "find the origin/corner of the currentWidget
+    "
+    |view viewId lastId point|
+
+    viewId := rootView id.
+    point  := aPoint + (device translatePoint:0@0 from:(self id) to:viewId).
+
+    inputView lower.
+
+    [viewId notNil] whileTrue:[
+        lastId := viewId.
+        viewId := device viewIdFromPoint:point in:lastId
+    ].
+
+    inputView raise.
+
+    view := device viewFromId:lastId.
+
+    view ~~ inputView ifTrue:[^ view]
+                     ifFalse:[^ nil]
+
+
+!
+
+isPoint:aPoint containedIn:aView
+    "checks whether a point is covered by a view.
+    "
+    |org ext|
+
+    org := aView computeOrigin.
+    ext := aView computeExtent.
+
+    ^ ((org extent:ext) containsPoint:aPoint)
 !
 
-!UIObjectView::UndoHistory class methodsFor:'instance creation'!
+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'!
+
+addToSelection:something
+    (testMode or:[something == selection]) ifFalse:[
+        super addToSelection:something.
+        self changed:#selection.
+    ]
+!
+
+inspectSelection
+    self singleSelectionDo:[:aView |
+        aView inspect
+    ]
+!
+
+removeFromSelection:something
+    super removeFromSelection:something.
+    self changed:#selection
+
+!
+
+select:something
+    (testMode or:[something == selection]) ifFalse:[
+        super select:something.
+        self changed:#selection
+    ]
+
+!
+
+selection
+    ^ selection
+
+
+!
+
+selectionFindMinimum:aOneArgBlock
+    "returns the minimum value from the block evaluated on each view
+     in the selection
+    "
+    |min val|
+
+    self selectionDo:[:aView|
+        val := aOneArgBlock value:aView.
+
+        min isNil ifTrue:[min := val]
+                 ifFalse:[min := min min:val]
+    ].
+    ^ min
+!
+
+selectionHiddenDo:aBlock
+    "apply block to every object in selection"
+
+    self selectionDo:[:aView |
+        self showUnselected:aView.
+    ].
+    device flush.
+    aBlock value.
+    self selectionDo:[:aView |
+        self showSelected:aView
+    ]
+
+
+!
+
+singleSelection
+    "returns single selection or nil
+    "
+    (selection isKindOf:SimpleView) ifTrue:[^ selection]
+                                   ifFalse:[^ nil]
+!
+
+singleSelectionDo:aBlock
+
+    self singleSelection notNil ifTrue:[
+        aBlock value:selection
+    ]
+!
+
+unselect
+    selection notNil ifTrue:[
+        super unselect.
+        self changed:#selection
+    ]
+
+!
+
+withSelectionHiddenDo:aBlock
+    "evaluate aBlock while selection is hidden"
+
+    |sel|
+
+    selection isNil ifTrue:[
+        aBlock value
+    ] ifFalse:[
+        sel := selection.
+        super unselect.
+        aBlock value.
+        super select:sel
+    ]
+
+    "Modified: 6.9.1995 / 01:46:16 / claus"
+
+
+! !
+
+!UIObjectView methodsFor:'testing'!
+
+canMove:something
+    ^ true
+
+
+!
+
+isHorizontalResizable:aComponent
+    ^ self subclassResponsibility
+
+
+!
+
+isVerticalResizable:aComponent
+    ^ self subclassResponsibility
+
+
+! !
+
+!UIObjectView methodsFor:'user actions'!
+
+createWidgetWithClass:aClass
+    "prepare to create new widgets
+    "
+    createClass := aClass.
+    pressAction := [:pressPoint | self startCreate:pressPoint].
+    self cursor:Cursor origin.
+
+
+!
+
+undoAction
+    undoHistory notEmpty ifTrue:[
+        self unselect.
+        undoHistory undoLast
+    ]
+
+
+! !
+
+!UIObjectView methodsFor:'user actions - dimension'!
+
+copyExtent
+    (selection isNil or:[selection isKindOf:Collection]) ifTrue:[
+        ^ self warn:'exactly one element must be selected'.
+    ].
+    copiedExtent := selection computeExtent
+
+
+
+!
+
+pasteExtent
+    copiedExtent notNil ifTrue:[
+        self transition:'paste extent' dimensionDo:[:v|
+            self resize:v corner:(v computeOrigin + copiedExtent)
+        ]    
+    ]    
+!
+
+pasteHeight
+    copiedExtent notNil ifTrue:[
+        self transition:'paste height' dimensionDo:[:v|
+            self resize:v bottom:(v computeOrigin + copiedExtent)
+        ]    
+    ]    
+
+!
+
+pasteWidth
+    copiedExtent notNil ifTrue:[
+        self transition:'paste width' dimensionDo:[:v|
+            self resize:v right:(v computeOrigin + copiedExtent)
+        ]    
+    ]    
+
+!
+
+setDimension:aLayout
+    |undoText|
+
+    undoText := 'change layout'.
+    aLayout isLayout ifTrue:[
+        undoText := 'change to layout frame'.
+        aLayout isAlignmentOrigin ifTrue:[
+            undoText := 'change to layout alignOrigin'.
+        ] ifFalse:[
+            aLayout isAlignmentOrigin ifTrue:[
+                undoText := 'change to layout origin'.
+            ]
+        ]
+    ].
+
+    self transition:undoText dimensionDo:[:v| v geometryLayout:(aLayout copy)]    
+
+!
+
+setToDefaultExtent
+    self transition:'default extent' dimensionDo:[:v|
+        self resize:v corner:(v computeOrigin + (v preferredExtent))
+    ]    
+
+!
+
+setToDefaultHeight
+    self transition:'default height' dimensionDo:[:v|
+        self resize:v bottom:(v computeOrigin + (v preferredExtent))
+    ]    
+
+!
+
+setToDefaultWidth
+    self transition:'default width' dimensionDo:[:v|
+        self resize:v right:(v computeOrigin + (v preferredExtent))
+    ]    
+
+!
+
+transition:what dimensionDo:aOneArgBlock
+    "change dimension within a transaction for the selected elements by evaluating
+     the block with the argument a view.
+    "
+    self selectionHiddenDo:[
+        undoHistory transactionNamed:what do:[
+            self selectionDo:[:aView|
+                self undoBlockDimensionChanged:aView.
+                aOneArgBlock value:aView.
+                self elementChangedLayout:aView.
+            ]
+        ]
+    ]
+! !
+
+!UIObjectView methodsFor:'user actions - move'!
+
+basicMoveSelectionHorizontal:n
+    "move left:  n < 0
+     move right: n > 0
+    "
+    self selectionHiddenDo:[
+        undoHistory transactionNamed:'move' do:[
+            self selectionDo:[:aView|self shifLayout:aView left:n right:n]
+        ].
+        self changed:#layout
+    ]
+
+
+!
+
+basicMoveSelectionVertical:n
+    "move up:   n < 0
+     move down: n > 0
+    "
+    self selectionHiddenDo:[
+        undoHistory transactionNamed:'move' do:[
+            self selectionDo:[:aView| self shifLayout:aView top:n bottom:n ]
+        ].
+        self changed:#layout
+    ]
+
+
+
+!
+
+moveObject:anObject to:aPoint
+    "move anObject to newOrigin, aPoint
+    "
+    |dX dY org delta|
+
+    anObject notNil ifTrue:[
+        org := anObject computeOrigin.
+
+        delta := aPoint - org.
+        delta := (self alignToGrid:aPoint) - org.
+        dX := delta x.
+        dY := delta y.
+
+        undoHistory disabledTransitionDo:[
+            self shifLayout:anObject top:dY bottom:dY left:dX right:dX
+        ].
+        self elementChangedLayout:anObject.
+    ]
+
+!
+
+moveSelectionDown
+    self moveSelectionDown:1
+
+
+!
+
+moveSelectionDown10
+    self moveSelectionDown:10
+
+
+!
+
+moveSelectionDown:n
+    self basicMoveSelectionVertical:n
+
+
+!
+
+moveSelectionLeft
+    self moveSelectionLeft:1
+
+
+!
+
+moveSelectionLeft10
+    self moveSelectionLeft:10
+
+
+!
+
+moveSelectionLeft:n
+    self basicMoveSelectionHorizontal:(n negated)
+
+
+!
+
+moveSelectionRight
+    self moveSelectionRight:1
+
+
+!
+
+moveSelectionRight10
+    self moveSelectionRight:10
+
+
+!
+
+moveSelectionRight:n
+    self basicMoveSelectionHorizontal:n
+
+
+!
+
+moveSelectionUp
+    self moveSelectionUp:1
+
+
+!
+
+moveSelectionUp10
+    self moveSelectionUp:10
+
+
+!
+
+moveSelectionUp:n
+    self basicMoveSelectionVertical:(n negated)
+
+
+! !
+
+!UIObjectView methodsFor:'user actions - position'!
 
-new
-    ^ self basicNew initialize
+alignSelectionBottom
+    |bmost delta|
+
+    self selectionHiddenDo:[
+        bmost := 0.
+        self selectionDo:[:v| bmost := bmost max:(v computeCorner y)].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v|
+                (delta := bmost - (v computeCorner y)) ~~ 0 ifTrue:[
+                    self shifLayout:v top:delta bottom:delta
+                ]
+            ]
+        ].
+        self changed:#layout
+    ]
+
+
+
+!
+
+alignSelectionCenterHor
+    |counter centerX|
+
+    self selectionHiddenDo:[
+        counter := 0.
+        centerX := 0.
+
+        self selectionDo:[:v |
+            centerX := centerX + (v computeCorner x + v computeOrigin x).
+            counter := counter + 1.
+        ].
+        centerX := centerX // (counter * 2).
+
+        undoHistory transactionNamed:'align' do:[
+            |newX oldX delta|
+
+            self selectionDo:[:v|
+                oldX  := v computeOrigin x.
+                newX  := centerX - ((v computeCorner x - oldX) // 2).
+                delta := newX - oldX.
+
+                self shifLayout:v left:delta right:delta
+            ]
+        ].
+        self changed:#layout
+    ]
+
+
+
+!
+
+alignSelectionCenterVer
+    |counter centerY|
+
+    self selectionHiddenDo:[
+        counter := 0.
+        centerY := 0.
+
+        self selectionDo:[:v |
+            centerY := centerY + (v computeCorner y + v computeOrigin y).
+            counter := counter + 1.
+        ].
+        centerY := centerY // (counter * 2).
+
+        undoHistory transactionNamed:'align' do:[
+            |newY oldY delta|
+
+            self selectionDo:[:v|
+                oldY  := v computeOrigin y.
+                newY  := centerY - ((v computeCorner y - oldY) // 2).
+                delta := newY - oldY.
+
+                self shifLayout:v top:delta bottom:delta
+            ]
+        ].
+        self changed:#layout
+    ]
+!
+
+alignSelectionLeft
+    |lmost delta|
+
+    self selectionHiddenDo:[
+        lmost := self selectionFindMinimum:[:v| v computeOrigin x].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v|
+                (delta := lmost - (v computeOrigin x)) ~~ 0 ifTrue:[
+                    self shifLayout:v left:delta right:delta
+                ]
+            ]
+        ].
+        self changed:#layout
+    ]
+
+!
+
+alignSelectionLeftAndRight
+    |lmost rmost|
+
+    self selectionHiddenDo:[
+        lmost := self selectionFindMinimum:[:v| v computeOrigin x].
+        rmost := 0.
+        self selectionDo:[:v | rmost := rmost max:(v computeCorner x)].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v|
+                self shifLayout:v left:(lmost - (v computeOrigin x))
+                                 right:(rmost - (v computeCorner x))
+            ]
+        ].
+        self changed:#layout
+    ]
+!
+
+alignSelectionRight
+    |rmost delta|
+
+    self selectionHiddenDo:[
+        rmost := 0.
+        self selectionDo:[:v| rmost := rmost max:(v computeCorner x)].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v|
+                (delta := rmost - (v computeCorner x)) ~~ 0 ifTrue:[
+                    self shifLayout:v left:delta right:delta
+                ]
+            ]
+        ].
+        self changed:#layout
+    ]
+
+!
+
+alignSelectionTop
+    |tmost delta|
+
+    self selectionHiddenDo:[
+        tmost := self selectionFindMinimum:[:v| v computeOrigin y].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v||delta|
+                (delta := tmost - (v computeOrigin y)) ~~ 0 ifTrue:[
+                    self shifLayout:v top:delta bottom:delta
+                ]
+            ]
+        ].
+        self changed:#layout
+    ]
+
+!
+
+alignSelectionTopAndBottom
+    |tmost bmost|
+
+    self selectionHiddenDo:[
+        tmost := self selectionFindMinimum:[:v| v computeOrigin y].
+        bmost := 0.
+        self selectionDo:[:v| bmost := bmost max:(v computeCorner y)].
+
+        undoHistory transactionNamed:'align' do:[
+            self selectionDo:[:v|
+                self shifLayout:v top:(tmost - (v computeOrigin y))
+                               bottom:(bmost - (v computeCorner y))
+            ]
+        ].
+        self changed:#layout
+    ]
+!
+
+centerSelection:aOneArgBlockXorY
+    "center selection horizontal or vertical dependant on the block result( x or y).
+     The argument to the block is the point.
+    "
+    |superview min max delta val|
+
+    self selectionHiddenDo:[
+        max := 0.
+
+        self selectionDo:[:aView |
+            superview isNil ifTrue:[
+                superview := aView superView
+            ] ifFalse:[
+                (aView superView == superview) ifFalse:[
+                    ^ self notify:'views must have same superview'.
+                ]
+            ].
+            val := aOneArgBlockXorY value:(aView computeOrigin).    
+
+            min isNil ifTrue:[min := val]
+                     ifFalse:[min := min min:val].
 
+            val := aOneArgBlockXorY value:(aView computeCorner).
+            max := max max:val.
+        ].
+
+        val := aOneArgBlockXorY value:(superview computeExtent).
+        max := (min + val - max) // 2.
+
+        max == min ifFalse:[
+            delta := max - min.
+
+            undoHistory transactionNamed:'center' do:[
+                self selectionDo:[:aView|
+                    self shifLayout:aView top:delta bottom:delta]
+            ]
+        ].
+        self changed:#layout
+    ]
+
+
+!
+
+centerSelectionHor
+    "center selection horizontal
+    "
+    self centerSelection:[:aPoint| aPoint x]
+
+
+!
+
+centerSelectionVer
+    "center selection vertical
+    "
+    self centerSelection:[:aPoint| aPoint y]
+!
+
+spreadSelectionHor
+    |sumWidths min max viewsInOrder topsInOrder count space|
+
+    (selection isKindOf:Collection) ifFalse:[^ self].
+
+    self selectionHiddenDo:[
+        count := 0.
+        sumWidths := 0.
+        max := 0.
+
+        self selectionDo:[:aView |
+            sumWidths := sumWidths + aView width.
+
+            min isNil ifTrue:[min := aView left]
+                     ifFalse:[min := min min:(aView left)].
+
+            max := max max:(aView right).
+            count := count + 1
+        ].
+        viewsInOrder := Array withAll:selection.
+        topsInOrder  := viewsInOrder collect:[:aView | aView left].
+        topsInOrder sortWith:viewsInOrder.
+
+        space := (((max - min) - sumWidths) / (count - 1)) rounded asInteger.
+
+        undoHistory transactionNamed:'spread' do:[
+            viewsInOrder do:[:aView | 
+                |delta|
+
+                delta := min - aView computeOrigin x.
+                self shifLayout:aView left:delta right:delta.
+                min := min + aView computeExtent x + space
+            ]
+        ].
+        self changed:#layout
+    ]
+
+!
+
+spreadSelectionVer
+    |sumHeights min max viewsInOrder topsInOrder count space|
+
+    (selection isKindOf:Collection) ifFalse:[^ self].
+
+    self selectionHiddenDo:[
+        count := 0.
+        sumHeights := 0.
+        max := 0.
+
+        self selectionDo:[:aView |
+            sumHeights := sumHeights + aView height.
+
+            min isNil ifTrue:[min := aView top]
+                     ifFalse:[min := min min:(aView top)].
+
+            max   := max max:(aView bottom).
+            count := count + 1
+        ].
+        viewsInOrder := Array withAll:selection.
+        topsInOrder  := viewsInOrder collect:[:aView|aView top].
+        topsInOrder sortWith:viewsInOrder.
+
+        space := (((max - min) - sumHeights) / (count - 1)) rounded asInteger.
+
+        undoHistory transactionNamed:'spread' do:[
+            viewsInOrder do:[:aView||delta|
+                delta := min - aView computeOrigin y.
+                self shifLayout:aView top:delta bottom:delta.
+                min := min + aView height + space
+            ]
+        ].
+        self changed:#layout
+    ]
+! !
+
+!UIObjectView methodsFor:'user actions - resize'!
+
+doDragResize:aPoint
+    "do a widget resize drag"
+
+    |p|
+
+    self invertOutlineOf:resizedObject.
+    p := (self alignToGrid:aPoint) - (resizedObject container originRelativeTo:self).
+    self perform:('x' , resizeSelector , ':') asSymbol with:p.
+    resizedObject geometryLayout:(resizedObject geometryLayout).
+    self invertOutlineOf:resizedObject
+
+    "Modified: 5.9.1995 / 17:11:46 / claus"
+
+!
+
+endResize
+    "cleanup after object resize"
+
+    self invertOutlineOf:resizedObject.
+    self setDefaultActions.
+    self select:resizedObject.
+    resizedObject := nil
+
+    "Modified: 5.9.1995 / 17:11:17 / claus"
+
+!
+
+startResizeBorder:b of:selection at:aPoint
+    "resize selected view
+    "
+    resizedObject := self singleSelection.
+
+    resizedObject notNil ifTrue:[
+        resizeSelector := b.
+        super unselect.
+
+        undoHistory transactionNamed:'extent' do:[
+            self undoBlockDimensionChanged:resizedObject.
+        ].
+
+        motionAction := [:movePoint | self doDragResize:movePoint].
+        releaseAction := [self endResize].
+        self invertOutlineOf:resizedObject
+    ]
+!
+
+xbottom:aPoint
+    self resize:resizedObject bottom:aPoint
+
+!
+
+xbottomLeft:aPoint
+    self resize:resizedObject   left:aPoint.
+    self resize:resizedObject bottom:aPoint.
+
+!
+
+xcorner:aPoint
+    self resize:resizedObject corner:aPoint.
+
+!
+
+xleft:aPoint
+    self resize:resizedObject left:aPoint
+
+!
+
+xorigin:aPoint
+    self resize:resizedObject left:aPoint.
+    self resize:resizedObject  top:aPoint.
+
+!
+
+xright:aPoint
+    self resize:resizedObject right:aPoint
+
+!
+
+xtop:aPoint
+    self resize:resizedObject top:aPoint
+
+!
+
+xtopRight:aPoint
+    self resize:resizedObject right:aPoint.
+    self resize:resizedObject   top:aPoint.
 
 ! !
 
@@ -24,6 +1568,20 @@
 
 ! !
 
+!UIObjectView::UndoHistory class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+
+!UIObjectView::UndoHistory class methodsFor:'instance creation'!
+
+new
+    ^ self basicNew initialize
+
+
+! !
+
 !UIObjectView::UndoHistory methodsFor:'accessing'!
 
 modifiedAction:aBlockWithOneArg
@@ -208,3 +1766,9 @@
 
 ! !
 
+!UIObjectView class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+
--- a/UIPainterView.st	Sat Feb 15 19:15:25 1997 +0100
+++ b/UIPainterView.st	Sat Feb 15 19:19:32 1997 +0100
@@ -1,10 +1,1406 @@
+"
+ COPYRIGHT (c) 1995 by Claus Gittinger
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+UIObjectView subclass:#UIPainterView
+        instanceVariableNames:'fontPanel code viewProperties superclassName className methodName
+                categoryName'
+        classVariableNames:'HandCursor'
+        poolDictionaries:''
+        category:'Interface-UIPainter'
+!
+
+Object subclass:#ViewProperty
+        instanceVariableNames:'aspectSelector changeSelector name nameIndex view elementClass
+                labelSelector identifier'
+        classVariableNames:'Identifier'
+        poolDictionaries:''
+        privateIn:UIPainterView
+!
+
 UIPainterView::ViewProperty subclass:#GroupProperties
-	instanceVariableNames:'controlledObjects group'
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:UIPainterView
+        instanceVariableNames:'controlledObjects group'
+        classVariableNames:''
+        poolDictionaries:''
+        privateIn:UIPainterView
+!
+
+!UIPainterView class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1995 by Claus Gittinger
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    not yet finished, not yet published, not yet released.
+"
+! !
+
+!UIPainterView methodsFor:'accessing'!
+
+className
+    ^ className
+
+    "Modified: 5.9.1995 / 18:41:30 / claus"
+!
+
+className:aString
+    className := aString
+
+    "Modified: 5.9.1995 / 18:47:17 / claus"
+!
+
+methodName
+    ^ methodName
+
+    "Modified: 5.9.1995 / 18:41:34 / claus"
+!
+
+methodName:aString
+    methodName := aString
+
+    "Modified: 5.9.1995 / 18:47:27 / claus"
+! !
+
+!UIPainterView methodsFor:'builder interface'!
+
+application
+    self halt.
+    ^ nil
+
+    "Modified: 6.9.1995 / 00:46:44 / claus"
+!
+
+aspectAt:aSymbol
+    self halt.
+    ^ nil
+
+    "Modified: 6.9.1995 / 00:45:35 / claus"
+!
+
+createdComponent:newView forSpec:aSpec
+    "callBack from UISpec view building"
+
+    |props|
+
+    props := self propertiesForNewView:newView.
+
+    aSpec name notNil ifTrue:[
+        (self propertyOfName:(aSpec name)) isNil ifTrue:[
+            props name:aSpec name
+        ]
+    ].
+
+    props labelSelector:(aSpec labelSelector).
+    props aspectSelector:(aSpec modelSelector).
+
+    viewProperties add:props.
+! !
+
+!UIPainterView methodsFor:'code manipulation'!
+
+changeClass
+    |box classNameHolder superclassNameHolder|
+
+    classNameHolder := (className ? 'MyClass') asValue.
+    superclassNameHolder := (superclassName ? 'ApplicationModel') asValue.
+
+    box := DialogBox new.
+    box addTextLabel:'class:'.
+    box addInputFieldOn:classNameHolder.
+    box addTextLabel:'super class:'.
+    box addInputFieldOn:superclassNameHolder.
+    box addAbortButton; addOkButton.
+
+    box open.
+
+    box accepted ifTrue:[
+        className := classNameHolder value.
+        superclassName := superclassNameHolder value.
+    ].
+
+
+
+
+
+
+!
+
+changeVariables
+    | box names propList p n newName|
+
+    names := VariableArray new.
+    propList := VariableArray new.
+    viewProperties do:[:props |
+        n := props name.
+        n notNil ifTrue:[
+            names add:n.
+            propList add:props
+        ]
+    ].
+    box := BuilderVariablesBox new.
+    box list:names.
+    box selectAction:[:selection |
+        p := propList at:selection
+    ].
+    box okAction:[
+        newName := box enterValue.
+Transcript showCR:('renamed ' , (p name) , 'to:' , newName).
+        p name:newName
+    ].
+    box showAtPointer
+
+
+
+! !
+
+!UIPainterView methodsFor:'creating subviews'!
+
+addProperties:properties for:aView
+    "set properties to a view and add properties to viewProperties.
+     In case that properties are nil properties are created
+    "
+    |name props|
+
+    (props := properties) isNil ifTrue:[
+        props := self propertiesForNewView:aView.
+    ].
+
+    viewProperties add:props.
+    name := props name.
+
+    (aView respondsTo:#label:) ifTrue:[
+        aView label:name
+    ].
+    aView name:name.
+  ^ props
+!
+
+propertiesForNewView:aView
+    |cls props index|
+
+    cls := aView class.
+
+    props := ViewProperty new.
+    props view:aView.
+    props elementClass:cls.
+    index := self variableIndexForClass:cls.
+    props nameIndex:index.
+    props name:(self variableNameForClass:cls index:index).
+
+"/    props initCode:nil.       --- add user-defined init code later
+
+    ^ props
+!
+
+setupCreatedObject:anObject
+    "set default properties for a created object
+    "
+    |props|
+
+    props := self addProperties:nil for:anObject.
+    self undoCreate:(props identifier).
+! !
+
+!UIPainterView methodsFor:'cut & paste'!
+
+convertForPaste:something
+    ^ nil
+
+
+!
+
+copySelection
+    "copy the selection into the cut&paste-buffer
+    "
+    |tmp|
+
+    tmp := OrderedCollection new.
+
+    self selectionDo:[:aView||topSpec|
+        topSpec := aView specClass 
+                        fromView:aView 
+                        callBack:[:spec :aSubView | 
+                                aSubView geometryLayout:(aSubView geometryLayout copy)
+                        ].
+        tmp add:topSpec.
+    ].
+
+    self setSelection:tmp
+
+!
+
+deleteSelection
+    "delete the selection
+    "
+    undoHistory transactionNamed:'delete' do:[
+        super deleteSelection
+    ].
+
+
+!
+
+pasteBuffer
+    "add the objects in the paste-buffer
+    "
+    |sel firstEntry builder|
+
+    sel := self getSelection.
+    self unselect.
+
+    sel size == 0 ifTrue:[firstEntry := sel]
+                 ifFalse:[firstEntry := sel at:1].
+
+    (firstEntry isKindOf:UISpecification) ifFalse:[
+        ^ self
+    ].
+    builder   := UIBuilder new.
+    selection := OrderedCollection new.
+
+    sel do:[:aSpec|
+        builder componentCreationHook:[:view :spec :aBuilder |
+            self createdComponent:view forSpec:spec
+        ].
+        builder applicationClass:(Smalltalk classNamed:className).
+        selection add:(aSpec buildViewWithLayoutFor:builder in:self).
+    ].
+
+    undoHistory transactionNamed:'paste' do:[
+        selection do:[:aView| |props|
+            props := self propertyOfView:aView.
+            self undoCreate:(props identifier)
+        ]
+    ].
+
+    selection size == 1 ifTrue:[
+        selection := selection at:1
+    ].
+    self showSelection.
+    self realizeAllSubViews.
+    inputView raise.
+    self changed:#tree
+
+! !
+
+!UIPainterView methodsFor:'generating output'!
+
+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 , '\\'.
+
+    code := code , (defCode withCRs)
+
+
+
+!
+
+generateCode
+    code := ''.
+    (Smalltalk classNamed:className) isNil ifTrue:[
+        self generateClassDefinition.
+    ].
+"/    self generateInitMethod.
+    code := code , self generateWindowSpec.
+    self generateOutlets.
+
+
+    ^ code withCRs
+
+    "Modified: 5.9.1995 / 20:57:53 / claus"
+! !
+
+!UIPainterView ignoredMethodsFor:'generating output'!
+
+generateInitCodeForGroup:aGroup
+    |c name p objects outlets moreCode sym typ val|
+
+    " <name> := <GroupClass> in:<name-of-superview>"
+
+    p := self propertyOfGroup:aGroup.
+    name := p at:#variableName.
+    c := '  ' , name , ' := ' , (aGroup class name) , ' new.\'.
+
+    code := code , c withCRs.
+
+    " <name> <symbol>:<value>"
+
+    objects := p at:#controlledObjects ifAbsent:[nil].
+    objects notNil ifTrue:[
+        objects do:[:controlledObject |
+            c := c , name , ' add:' , (self variableNameOf:controlledObject) , '.\'
+        ]
+    ].
+
+    code := code , c withCRs
+
+
+
+
+
+!
+
+generateInitCodeForOtherStuff
+    |g c name p outlets moreCode sym typ val|
+
+    "generate code for groups"
+
+    viewProperties do:[:props |
+        g := props at:#group ifAbsent:[nil].
+        g notNil ifTrue:[
+            self generateInitCodeForGroup:g
+        ]
+    ]
+
+
+!
+
+generateInitCodeForView:aView
+    |c name p outlets moreCode sym typ val|
+
+    " <name> := <ViewClass> in:<name-of-superview>"
+
+    p := self propertyOfView:aView.
+    name := p at:#variableName.
+    c := '    ' , name , ' := ' ,
+         (aView class name) , ' in:' , (self variableNameOf:(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 |
+        self generateInitCodeForView:v
+    ]
+
+    "Modified: 5.9.1995 / 20:06:07 / claus"
+!
+
+generateInitMethod
+    |defCode|
+
+    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 := code , defCode withCRs.
+
+    self subviewsOf:self do:[:v |
+        self generateInitCodeForView:v
+    ].
+
+    self generateInitCodeForOtherStuff.
+
+    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
+
+
+
+
+
+! !
+
+!UIPainterView methodsFor:'generating output'!
+
+generateOutlets
+    ^ self
+!
+
+generateWindowSpec
+    |spec specArray str|
+
+    subViews remove:inputView.
+    [
+        spec := FullSpec fromView:self callBack:[:newSpec :view | self stuffPropertiesFrom:view intoSpec:newSpec].
+    ] valueNowOrOnUnwindDo:[
+        subViews addFirst:inputView.
+    ].
+
+    specArray := spec literalArrayEncoding.
+    str := WriteStream on:String new.
+    self prettyPrintSpecArray:specArray on:str indent:5.
+
+    code := Character excla asString 
+            , className , ' class methodsFor:''interface specs'''
+            , Character excla asString , '\\'
+
+            , methodName , '\'
+            , '    "this window spec was automatically generated by the ST/X UIPainter"\\'
+            , '    "do not manually edit this - the painter/builder may not be able to\'
+            , '     handle the specification if its corrupted."\\'
+            , '    "UIPainter new openOnClass:' , className , ' andSelector:#' , methodName , '"\'
+            , '    "' , className , ' new openInterface:#' , methodName , '"\'.
+
+    methodName = 'windowSpec' ifTrue:[
+        code := code , '    "' , className , ' open"\'
+    ].
+    code := code 
+            , '\'
+            , '    <resource: #canvas>\\'
+            , '    ^\' 
+            , '     ', str contents
+            , '\'
+            , Character excla asString
+            , ' '
+            , Character excla asString
+            , '\\'.
+
+    ^ code withCRs
+
+    "Modified: 5.9.1995 / 21:01:35 / claus"
+!
+
+nameOfClass
+    ^ 'NewView'
+!
+
+outletValueOf:aSymbol for:aView
+"/    |c name p outlets moreCode sym typ val|
+"/
+"/    p := self propertyOfView:aView.
+"/    outlets := p at:#outlets ifAbsent:[^ nil].
+"/    outlets notNil ifTrue:[
+"/        outlets do:[:selectorOutlet |
+"/            sym := selectorOutlet at:#selector.
+"/            (sym == aSymbol) ifTrue:[
+"/                typ := selectorOutlet at:#type.
+"/                val := selectorOutlet at:#value.
+"/                ^ val
+"/            ]
+"/        ]
+"/    ].
+    ^ nil
+
+
+
+
+!
+
+prettyPrintSpecArray:spec on:aStream indent:i
+    "just for your convenience: prettyPrint a specArray to aStream - it looks better that way"
+
+    |what oneLine|
+
+    spec isArray ifFalse:[
+        spec isLiteral ifTrue:[
+            aStream nextPutAll:spec storeString
+        ] ifFalse:[
+            self halt.
+        ].
+        ^ self
+    ].
+
+    spec isEmpty ifTrue:[
+        aStream nextPutAll:'#()'.
+        ^ self
+    ].
+
+    what := spec at:1.
+    what isArray ifTrue:[
+        aStream cr; spaces:i+2.
+        aStream nextPutAll:'#('.
+        "/ a spec-collection
+        spec do:[:element |
+            self prettyPrintSpecArray:element on:aStream indent:i+2.
+        ].
+        aStream cr.
+        aStream spaces:i+1.
+        aStream nextPutAll:')'.
+        ^ self.
+    ].
+
+    oneLine := false.
+    (#(#LayoutFrame #LayoutOrigin #AlignmentOrigin 
+       #Rectangle #Point
+       #Color #ColorValue
+    ) 
+    includesIdentical:what) ifTrue:[
+        oneLine := true
+    ].
+
+    oneLine ifFalse:[
+        aStream cr.
+        aStream spaces:i+2.
+    ].
+    aStream nextPutAll:'#('.
+
+
+    aStream nextPutAll:what storeString.
+
+    oneLine ifFalse:[
+        aStream cr.
+        aStream spaces:i+4.
+    ].
+
+    2 to:spec size do:[:index |
+        aStream space.
+        self prettyPrintSpecArray:(spec at:index) on:aStream indent:i+4.
+        oneLine ifFalse:[
+            (index odd and:[index ~~ (spec size)]) ifTrue:[
+                aStream cr; spaces:i+4.
+            ]
+        ]
+    ].
+    oneLine ifFalse:[
+        aStream cr.
+        aStream spaces:i+1.
+    ].
+    aStream nextPutAll:')'.
+
+    "Modified: 5.9.1995 / 17:44:20 / claus"
+!
+
+storeContentsOn:aStream
+    viewProperties do:[:p| p storeOn:aStream]
+!
+
+stuffPropertiesFrom:view intoSpec:newSpec
+    "stuff any additional information (held in the properties) into the spec
+     which was just created from view"
+
+    |props aspectSelector changeSelector labelSelector name|
+
+    props := self propertyOfView:view.
+    props isNil ifTrue:[^ self].
+
+    (aspectSelector := props aspectSelector) notNil ifTrue:[
+        newSpec model:aspectSelector
+    ].
+    (changeSelector := props changeSelector) notNil ifTrue:[
+        newSpec change:changeSelector
+    ].
+    (labelSelector := props labelSelector) notNil ifTrue:[
+        newSpec label:labelSelector
+    ].
+    (name := props name) notNil ifTrue:[
+        newSpec name:name
+    ].
+
+!
+
+subviewVariableNames
+    |names|
+
+    names := ''.
+    viewProperties do:[:p| names := names , ' ' , (p name)].
+  ^ names
 !
 
+subviewsOf:aView do:aBlock
+    |subs v|
+
+    (subs := aView subViews) notNil ifTrue:[
+        subs do:[:v|
+            (v ~~ inputView and:[v notNil]) ifTrue:[
+                (viewProperties detect:[:p | p view == v] ifNone:nil) notNil ifTrue:[ 
+                    (v superView == aView) ifTrue:[
+                        aBlock value:v
+                    ]
+                ]
+            ]
+        ]
+    ]
+
+! !
+
+!UIPainterView methodsFor:'group manipulations'!
+
+groupEnterFields
+    |props name index group objects|
+
+    selection isNil ifTrue:[^ self].
+    self selectionDo:[:aView |
+        (aView isKindOf:EditField) ifFalse:[
+            self warn:'select EditFields only !!'.
+            ^ self
+        ]
+    ].
+    self selectionHiddenDo:[
+        group := EnterFieldGroup new.
+
+        props := GroupProperties new.
+        props elementClass:EnterFieldGroup.
+        props group:group.
+        index := self variableIndexForClass:EnterFieldGroup.
+        props nameIndex:index.
+        name := self variableNameForClass:EnterFieldGroup index:index.
+        props name:name.
+        objects := OrderedCollection new.
+        props controlledObjects:objects.
+        viewProperties add:props.
+
+        self selectionDo:[:aView |
+            objects add:aView.
+            group add:aView
+        ].
+    ]
+
+
+!
+
+groupRadioButtons
+    |props name index group objects|
+
+    selection isNil ifTrue:[^ self].
+    self selectionDo:[:aView |
+        (aView isKindOf:RadioButton) ifFalse:[
+            self warn:'select RadioButtons only !!'.
+            ^ self
+        ]
+    ].
+    self selectionHiddenDo:[
+        group := RadioButtonGroup new.
+
+        props := GroupProperties new.
+        props elementClass:RadioButtonGroup.
+        props group:group.
+        index := self variableIndexForClass:RadioButtonGroup.
+        props nameIndex:index.
+        name := self variableNameForClass:RadioButtonGroup index:index.
+        props name:name.
+        group groupID:name asSymbol.
+        objects := OrderedCollection new.
+        props controlledObjects:objects.
+        viewProperties add:props.
+
+        self selectionDo:[:aView |
+            aView turnOff.
+            objects add:aView.
+            group add:aView
+        ].
+    ]
+
+    "Modified: 5.9.1995 / 16:06:15 / claus"
+! !
+
+!UIPainterView methodsFor:'initialization'!
+
+initialize
+    super initialize.
+
+    superclassName := 'ApplicationModel'.
+    className      := 'NewApplication'.
+    methodName     := 'windowSpec'.
+    categoryName   := 'Applications'.
+
+    viewProperties := OrderedCollection new.
+    HandCursor     := Cursor leftHand.
+
+    "Modified: 5.9.1995 / 19:58:06 / claus"
+!
+
+initializeMiddleButtonMenu
+    |labels|
+
+    labels := resources array:#(
+                        'copy'
+                        'cut'
+                        'paste'
+                        '-'
+                        'save'
+                        'print'
+                        '-'
+                        'inspect'
+                      ).
+
+    self middleButtonMenu:(PopUpMenu
+                                labels:labels
+                             selectors:#(
+                                         copySelection
+                                         deleteSelection
+                                         pasteBuffer
+                                         nil               
+                                         save
+                                         print
+                                         nil               
+                                         inspectSelection
+                                        )
+                                receiver:self
+                                     for:self)
+
+! !
+
+!UIPainterView methodsFor:'interface to Builder'!
+
+addOutletDefinitionFor:outletSymbol type:type value:outletValue for:aView
+    |outletProps selectorProps viewProps|
+
+    viewProps := self propertyOfView:aView.
+"/    outletProps := viewProps at:#outlets ifAbsent:[nil].
+"/    outletProps isNil ifTrue:[
+"/        outletProps := Dictionary new.
+"/        viewProps at:#outlets put:outletProps
+"/    ].
+"/    selectorProps := outletProps at:outletSymbol ifAbsent:[nil].
+"/    selectorProps isNil ifTrue:[
+"/        selectorProps := Dictionary new.
+"/        outletProps at:outletSymbol put:selectorProps
+"/    ].
+"/
+"/    selectorProps at:#selector put:outletSymbol.
+"/    selectorProps at:#type put:type.
+"/    selectorProps at:#value put:outletValue
+
+!
+
+addSpec:specOrSpecArray
+    |spec builder|
+
+    spec := UISpecification from:specOrSpecArray.
+
+    builder := UIBuilder new.
+    builder componentCreationHook:[:view :spec :aBuilder |
+                self createdComponent:view forSpec:spec
+            ].
+    builder applicationClass:(Smalltalk classNamed:className).
+    spec setupView:self for:builder.
+    self realizeAllSubViews.
+    inputView raise.
+
+"/    viewProperties := OrderedCollection new.
+"/    self generatePropertiesFor:(self subViews select:[:v | v ~~ inputView]).
+
+    self changed:#tree.
+
+
+    "Modified: 5.9.1995 / 23:36:55 / claus"
+!
+
+applicationName
+    ^ className
+!
+
+aspectSelectorForView:aView
+    |props aspect|
+
+    props := self propertyOfView:aView.
+    props isNil ifTrue:[^ nil].
+    ^ props aspectSelector
+
+!
+
+changeSelectorForView:aView
+    |props aspect|
+
+    props := self propertyOfView:aView.
+    props isNil ifTrue:[^ nil].
+"/    ^ props changeSelector
+    ^ nil
+!
+
+generatePropertiesFor:aCollectionOfViews
+
+    "/ done as two loops, to get bread-first naming
+
+    aCollectionOfViews do:[:aView|
+        |props|
+
+        props := self propertiesForNewView:aView.
+        viewProperties add:props.
+        aView name:(props name).
+
+        aView geometryLayout isNil ifTrue:[
+            aView geometryLayout:(aView bounds asLayout).
+        ]
+    ].
+
+    aCollectionOfViews do:[:aView |
+        |subs|
+
+        subs := aView subViews.
+        subs notNil ifTrue:[
+            self generatePropertiesFor:subs
+        ]
+    ].
+
+!
+
+inspectAttributes
+    |p|
+
+    self singleSelectionDo:[:aView |
+        p := self propertyOfView:aView.
+        p inspect
+    ]
+!
+
+setAspectSelector:aspectSymbol forView:aView
+    |props|
+
+    props := self propertyOfView:aView.
+
+    undoHistory transactionNamed:'aspect' do:[
+        self selectionDo:[:aView|
+            undoHistory isTransactionOpen ifTrue:[
+                |oldAspect|
+
+                oldAspect := props aspectSelector.
+                undoHistory addUndoBlock:[
+                    props aspectSelector:oldAspect.
+                    self elementChanged:aView.
+                ]
+            ].
+        ].
+    ].
+
+    props aspectSelector:aspectSymbol
+
+!
+
+setChangeSelector:changeSymbol forView:aView
+    |props|
+
+    props := self propertyOfView:aView.
+    props changeSelector:changeSymbol
+
+!
+
+setupFromSpec:specOrSpecArray
+    self removeAll.
+    self addSpec:specOrSpecArray
+!
+
+showFontPanel
+    |action|
+
+    fontPanel isNil ifTrue:[
+        fontPanel := FontPanel new 
+    ].
+
+    selection notNil ifTrue:[
+        action := [:family :face :style :size |
+                       self changeFontFamily:family face:face
+                                       style:style size:size
+                  ].
+        fontPanel action:action.
+        fontPanel showAtPointer
+    ]
+! !
+
+!UIPainterView methodsFor:'misc'!
+
+changeFontFamily:family face:face style:style size:size
+    |f|
+
+    f := Font family:family
+                face:face
+               style:style
+                size:size.
+
+    f notNil ifTrue:[
+        self selectionHiddenDo:[
+            self selectionDo:[:aView |
+                aView font:f.
+                self elementChanged:aView.
+            ]
+        ]
+    ]
+
+    "Modified: 5.9.1995 / 12:13:27 / claus"
+!
+
+changeVariableNameOf:aView to:newName
+    |prop|
+
+    prop := self propertyOf:aView.
+
+    prop isNil ifTrue:[
+        ^ self error:'no such view'
+    ].
+
+    ((aView respondsTo:#label:) and:[aView label = prop name]) ifTrue:[
+        self selectionHiddenDo:[
+            |layout|
+            layout := aView geometryLayout copy.
+            aView label:newName.
+            aView geometryLayout:layout.
+        ]
+    ].
+
+    prop  name:newName.
+    aView name:newName.
+    self changed:#widgetName
+
+
+
+!
+
+variableIndexForClass:aClass
+    |max|
+
+    max := 0.
+
+    viewProperties do:[:p|
+        p elementClass == aClass ifTrue:[
+            max := max max:(p nameIndex)
+        ]
+    ].
+    ^ max + 1
+
+!
+
+variableNameForClass:aClass index:index
+    |n|
+
+    n := (aClass name) , index printString.
+    n at:1 put:(n at:1) asLowercase.
+  ^ n
+
+!
+
+variableNameOf:aView
+    |prop|
+
+    aView notNil ifTrue:[
+        prop := self propertyOf:aView
+    ].
+
+    prop notNil ifTrue:[^ prop name]
+               ifFalse:[^ 'self']
+
+! !
+
+!UIPainterView methodsFor:'private undo-actions'!
+
+undoCreate:aViewIdentifier
+
+    undoHistory isTransactionOpen ifTrue:[
+        undoHistory addUndoBlock:[
+            |props|
+
+            props := self propertyOfIdentifier:aViewIdentifier.
+
+            props notNil ifTrue:[
+                self removeObject:(props view)
+            ]
+        ]
+    ]
+!
+
+undoRemove:propertyOfView
+    |clsName layout parent aView|
+
+    undoHistory isTransactionOpen ifFalse:[
+        ^ self
+    ].
+
+    aView   := propertyOfView view.
+    clsName := aView class.
+    layout  := aView geometryLayout.
+    parent  := aView superView.
+
+    parent ~~ self ifTrue:[
+        parent := (self propertyOf:parent) identifier.
+    ] ifFalse:[
+        parent := nil
+    ].
+    propertyOfView view:nil.    
+
+    undoHistory addUndoBlock:[
+        |recreatedView props|
+
+        parent notNil ifTrue:[
+            props := self propertyOfIdentifier:parent.
+
+            props notNil ifTrue:[parent := props view]
+                        ifFalse:[parent := self]
+        ] ifFalse:[
+            parent := self
+        ].
+
+        recreatedView := clsName in:parent.
+        recreatedView geometryLayout:layout.
+        propertyOfView view:recreatedView.    
+        self addProperties:propertyOfView for:recreatedView.
+        recreatedView realize.
+        inputView raise.
+        self changed:#tree.
+    ].
+    aView := nil.
+
+! !
+
+!UIPainterView methodsFor:'removing components'!
+
+remove:something
+    "remove something, anObject or a collection of objects from the contents
+     do redraw"
+
+    self forEach:something do:[:anObject |
+        self removeObject:anObject
+    ]
+
+
+!
+
+removeAll
+    "remove the argument, anObject"
+
+    self unselect.
+
+    subViews notNil ifTrue:[
+        subViews copy do:[:sub |
+            sub ~~ inputView ifTrue:[   
+                self removeTreeFrom:sub
+            ]
+        ]
+    ].
+
+    viewProperties := OrderedCollection new.
+    undoHistory reinitialize.
+    self changed:#tree
+!
+
+removeObject:anObject
+    "remove the argument, anObject"
+
+    self removeTreeFrom:anObject.
+    self changed:#tree
+
+    "Modified: 5.9.1995 / 20:51:28 / claus"
+!
+
+removeTreeFrom:anObject
+    "remove the argument, anObject and all of its children
+    "
+    |props|
+
+    anObject notNil ifTrue:[
+        (anObject subViews notNil) ifTrue:[
+            anObject subViews copy do:[:sub |
+                self removeTreeFrom:sub
+            ]
+        ].
+        props := self propertyOf:anObject.
+        self undoRemove:props.
+        viewProperties remove:props.
+        anObject destroy
+    ]
+! !
+
+!UIPainterView methodsFor:'selections'!
+
+addNameToSelection:aString
+    |prop|
+
+    prop := self propertyOfName:aString.
+
+    prop notNil ifTrue:[
+        self addToSelection:(prop view)
+    ]
+
+!
+
+removeNameFromSelection:aString
+    |prop|
+
+    prop := self propertyOfName:aString.
+
+    prop notNil ifTrue:[
+        self removeFromSelection:(prop view)
+    ]
+
+!
+
+selectName:aStringOrCollection
+    |prop coll s|
+
+    (aStringOrCollection isNil or:[aStringOrCollection isEmpty]) ifTrue:[
+        ^ self unselect
+    ].
+
+    (s := aStringOrCollection) isString ifFalse:[
+        s size == 1 ifTrue:[
+            s := s first
+        ] ifFalse:[
+            coll := OrderedCollection new.
+
+            s do:[:aName|
+                (prop := self propertyOfName:aName) notNil ifTrue:[
+                    coll add:(prop view)
+                ]
+            ].
+            coll size == 1 ifTrue:[ ^ self select:(coll at:1) ].
+            coll size == 0 ifTrue:[ ^ self unselect ].
+
+            self hideSelection.
+            selection := coll.
+            self showSelection.
+          ^ self changed:#selection
+        ]
+    ].
+
+    prop := self propertyOfName:s.
+    prop isNil ifTrue:[^ self unselect]
+              ifFalse:[^ self select:(prop view)]
+
+! !
+
+!UIPainterView methodsFor:'seraching property'!
+
+propertyOf:something
+
+    ^ viewProperties detect:[:p| (p view == something or:[p group == something])]
+                     ifNone:nil
+
+
+
+
+
+!
+
+propertyOfGroup:aGroup
+
+    ^ viewProperties detect:[:p| p group == aGroup] ifNone:nil
+!
+
+propertyOfIdentifier:anIdentifier
+
+    ^ viewProperties detect:[:p| p identifier == anIdentifier] ifNone:nil.
+!
+
+propertyOfName:aString
+
+    aString = 'self' ifFalse:[
+        ^ viewProperties detect:[:p| p name = aString] ifNone:nil
+    ].
+    ^ nil
+!
+
+propertyOfView:aView
+
+    aView == self ifFalse:[
+        ^ viewProperties detect:[:p| p view == aView] ifNone:nil
+    ].
+    ^ nil
+! !
+
+!UIPainterView methodsFor:'testing'!
+
+isHorizontalResizable:aComponent
+
+    (aComponent isKindOf:ScrollBar) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    (aComponent isKindOf:Scroller) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    (aComponent isKindOf:Slider) ifTrue:[
+        ^ aComponent orientation == #horizontal
+    ].
+    ^ true
+
+
+!
+
+isVerticalResizable:aComponent
+
+    (aComponent isKindOf:EditField) ifTrue:[
+        ^ false
+    ].
+    (aComponent isKindOf:ScrollBar) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    (aComponent isKindOf:Scroller) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    (aComponent isKindOf:Slider) ifTrue:[
+        ^ aComponent orientation == #vertical
+    ].
+    ^ true
+
+
+! !
+
+!UIPainterView::ViewProperty class methodsFor:'instance creation'!
+
+new
+    Identifier notNil ifTrue:[Identifier := Identifier + 1]
+                     ifFalse:[Identifier := 1].
+
+  ^ self basicNew initialize
+! !
+
+!UIPainterView::ViewProperty methodsFor:'accessing'!
+
+aspectSelector
+    "return the value of the instance variable 'aspectSelector' (automatically generated)"
+
+    ^ aspectSelector
+!
+
+aspectSelector:something
+    "set the value of the instance variable 'aspectSelector' (automatically generated)"
+
+    aspectSelector := something.
+!
+
+changeSelector
+    "return the value of the instance variable 'changeSelector' (automatically generated)"
+
+    ^ changeSelector!
+
+changeSelector:something
+    "set the value of the instance variable 'changeSelector' (automatically generated)"
+
+    changeSelector := something.!
+
+elementClass
+    "return the value of the instance variable 'elementClass' (automatically generated)"
+
+    ^ elementClass!
+
+elementClass:something
+    "set the value of the instance variable 'elementClass' (automatically generated)"
+
+    elementClass := something.!
+
+group
+    ^ nil
+!
+
+identifier
+    "return the unique identifier assigned to property
+    "
+    ^ identifier
+!
+
+labelSelector
+    "return the value of the instance variable 'labelSelector' (automatically generated)"
+
+    ^ labelSelector!
+
+labelSelector:something
+    "set the value of the instance variable 'labelSelector' (automatically generated)"
+
+    labelSelector := something.!
+
+name
+    "return the value of the instance variable 'name' (automatically generated)"
+
+    ^ name!
+
+name:something
+    "set the value of the instance variable 'name' (automatically generated)"
+
+    name := something.!
+
+nameIndex
+    "return the value of the instance variable 'nameIndex' (automatically generated)"
+
+    ^ nameIndex!
+
+nameIndex:something
+    "set the value of the instance variable 'nameIndex' (automatically generated)"
+
+    nameIndex := 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::GroupProperties class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+
 !UIPainterView::GroupProperties methodsFor:'accessing'!
 
 controlledObjects
@@ -27,3 +1423,9 @@
 
     group := something.! !
 
+!UIPainterView class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+! !
+