UIObjectView.st
author Claus Gittinger <cg@exept.de>
Tue, 28 Oct 1997 20:41:44 +0100
changeset 352 088174fc1e71
parent 284 995078a58977
child 353 6687441ccd4d
permissions -rw-r--r--
support for constant lists; better aspect-method code added browse-aspect-methods

"
 COPYRIGHT (c) 1995 by eXept Software AG
              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.
"



ObjectView subclass:#UIObjectView
	instanceVariableNames:'saveSelection inputView enableChannel undoHistory copiedExtent
		copiedLayout resizeData clipChildren selectionHiddenLevel
		setOfSuperViewsSizeChanged'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

Object subclass:#UndoHistory
	instanceVariableNames:'startIdentifier identifier painter history transaction enabled'
	classVariableNames:''
	poolDictionaries:''
	privateIn:UIObjectView
!

Object subclass:#Transaction
	instanceVariableNames:'identifier type text actions'
	classVariableNames:''
	poolDictionaries:''
	privateIn:UIObjectView::UndoHistory
!

!UIObjectView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by eXept Software AG
              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
"
    buildIn view used by the UIPainter; it provides all services for creating, deleting
    moving and changing layouts of painted components on a canvas.

    [see also:]
        UIBuilder
        UIPainterView

    [author:]
        Claus Atzkern
"

! !

!UIObjectView class methodsFor:'conversion'!

asLayoutFrameFromView:aView
    "convert layout from aView to a frameLayout. On success the frameLayout is
     returned otherwise nil
    "
    |lF lO rF rO tF tO bF bO type layout newLyt|

    type   := self layoutType:aView.
    layout := aView geometryLayout.

    layout isNil ifTrue:[
        type == #Extent ifTrue:[
            layout := aView bounds asLayout
        ]
    ].

    (type isNil or:[layout isNil]) ifTrue:[
        ^ nil
    ].

    type == #LayoutFrame ifTrue:[
        ^ layout copy
    ].

    layout isLayout ifFalse:[
        type == #Rectangle ifTrue:[
            lO := layout left.
            tO := layout top.
            rO := layout right.
            bO := layout bottom.
        ] ifFalse:[
            lO := layout x.
            tO := layout y.
            rO := lO + aView extent x.
            bO := tO + aView extent y.
        ].

        ^ LayoutFrame leftFraction:0 offset:lO  rightFraction:0 offset:rO
                       topFraction:0 offset:tO bottomFraction:0 offset:bO
    ].

    lF := layout leftFraction.
    lO := layout leftOffset.
    tF := layout topFraction.
    tO := layout topOffset.
    bF := tF.
    bO := tO + aView extent y.
    rF := lF.
    rO := lO + aView extent x.

    newLyt := LayoutFrame leftFraction:lF offset:lO  rightFraction:rF offset:rO
                           topFraction:tF offset:tO bottomFraction:bF offset:bO.

    (    (type == #AlignmentOrigin)
     and:[layout leftAlignmentFraction ~~ 0
      or:[layout topAlignmentFraction  ~~ 0]]
    ) ifTrue:[
        |svRc prBd dlta|

        svRc := aView superView viewRectangle.
        prBd := aView preferredBounds.
        dlta := (  ((layout rectangleRelativeTo:svRc preferred:prBd) corner)
                 - ((newLyt rectangleRelativeTo:svRc preferred:prBd) corner)
                ) rounded.

        newLyt leftOffset:(lO + dlta x).
        newLyt rightOffset:(rO + dlta x).
        newLyt topOffset:(tO + dlta y).
        newLyt bottomOffset:(bO + dlta y).
    ].
  ^ newLyt.

    "Modified: 28.3.1997 / 19:52:48 / cg"
! !

!UIObjectView class methodsFor:'defaults'!

defaultGrid
    ^ 4 @ 4

!

gridShown
    ^ false

!

handleSize
    "size of blob drawn for handles"
    ^ 4

!

hitDelta
    ^ 4

! !

!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
    "
    |layout spec superView|

    aView notNil ifTrue:[
        layout := aView geometryLayout.
        layout notNil ifTrue:[
            layout isLayout ifTrue:[
                layout isLayoutFrame        ifTrue:[ ^ #LayoutFrame ].
                layout isAlignmentOrigin    ifTrue:[ ^ #AlignmentOrigin ].
                layout isLayoutOrigin       ifTrue:[ ^ #LayoutOrigin ].
            ] ifFalse:[
                layout isRectangle          ifTrue:[ ^ #Rectangle ].
                layout isPoint              ifTrue:[ ^ #Point ].
            ]
        ] ifFalse:[
            (superView := aView superView) notNil ifTrue:[
                spec := superView specClass.
                spec canResizeSubComponents ifTrue:[
                    ^ #Extent
                ]
            ]
        ]
    ].
    ^ nil

    "Modified: 28.2.1997 / 13:02:16 / cg"
! !

!UIObjectView methodsFor:'accessing'!

enableChannel
    "returns the channel which keeps false if running test otherwise true
    "
  ^ enableChannel
!

gridAlign
    "returns state of aligning to grid
    "
    ^ aligning

!

gridAlign:aBool
    "change state of aligning to grid
    "
    aBool ifTrue:[self alignOn]
         ifFalse:[self alignOff]

!

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)


!

gridShown:aBool
    "change visibility of grid
    "
    aBool ifTrue:[self showGrid]
         ifFalse:[self hideGrid]
!

hideGrid
    "hide grid
    "
    gridShown ifTrue:[
        self withSelectionHiddenDo:[super hideGrid]
    ]


!

showGrid
    "show grid
    "
    self withSelectionHiddenDo:[super showGrid]
! !

!UIObjectView methodsFor:'accessing behavior'!

enabled
    ^ enableChannel value
!

enabled:aState
    "set the modification / test mode
    "
    (aState == enableChannel value) ifFalse:[
        aState ifFalse:[
            saveSelection := self selection.
            self select:nil.
            enableChannel value:aState.
            inputView unmap.
        ] ifTrue:[
            inputView raise.
            inputView realize.
            enableChannel value:aState.
            self select:saveSelection.
        ]
    ]



!

resetModification
    "set modification state to false
    "
    undoHistory resetModification
!

testMode
    "returns true if running test
    "
    ^ enableChannel value not


!

testMode:aBoolean
    "change test mode
    "
    self enabled:(aBoolean not)
! !

!UIObjectView methodsFor:'blocked'!

addObject:anObject
    "add the argument, anObject to the contents - with redraw
    "
    self halt

!

addObjectWithoutRedraw:anObject
    "add the argument, anObject to the contents - with redraw
    "
    self halt

!

startCreate:aPoint
    self setDefaultActions.
    self halt
! !

!UIObjectView methodsFor:'event handling'!

elementChangedSize:aView
    "some element has changed its size; collect them during selectionHiddenLevel 
     is on
    "
    |spv|

    spv := self findContainerOfView:aView.

    selectionHiddenLevel ~~ 0 ifTrue:[setOfSuperViewsSizeChanged add:spv]
                             ifFalse:[spv sizeChanged:nil]
!

exposeX:x y:y width:w height:h
    "handle an expose event from device; redraw selection
    "
    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
        ]
    ]

!

keyPress:key x:x y:y
    "any key pressed
    "
    <resource: #keyboard ( #Delete #BackSpace #Cut #Copy #Paste ) >

    (key == #Cut or:[key == #Delete or:[key == #BackSpace]]) ifTrue: [
        ^ self deleteSelection
    ].

    key == #Copy  ifTrue:[ ^ self copySelection].
    key == #Paste ifTrue:[ ^ self pasteBuffer].
!

processEvent:anEvent
    "catch expose events for components, and redraw its handles after
     the redraw when this happens
    "
    (anEvent type == #damage and:[self isSelected:(anEvent view)]) ifTrue:[
        self showSelected:(anEvent view)
    ].
    ^ false.


!

sizeChanged:how
    "size of a view(s) changed
    "
    self withSelectionHiddenDo:[
        super sizeChanged:how
    ]


! !

!UIObjectView methodsFor:'initialization'!

initialize
    "setup attributes
    "
    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.
    setOfSuperViewsSizeChanged := IdentitySet new.

    inputView eventReceiver:self.
    inputView enableButtonEvents.
    inputView enableButtonMotionEvents.

    self setDefaultActions.

    undoHistory          := UndoHistory on:self.
    enableChannel        := true asValue.
    clipChildren         := true.
    selectionHiddenLevel := 0.

    (self class gridShown) ifTrue:[
        super showGrid
    ].

!

map
    "make the view visible on the screen and in case of a none empty
     selection the selection will be shown.
    "
    super map.
    self showSelection.
!

realize
    super realize.
    self windowGroup postEventHook:self

! !

!UIObjectView methodsFor:'misc'!

cursor:aCursor
    "set cursor
    "
    inputView realized ifTrue:[
        inputView cursor:aCursor
    ].
    super cursor:aCursor


!

invertOutlineOf:something
    "invert outline of an object or collection of objects
    "
    |wasClipped p|

    (wasClipped := clipChildren) ifTrue:[
        self clippedByChildren:(clipChildren := false).
    ].

    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).
    ].

!

minSetOfSuperViews:setOfViews

    setOfViews isCollection ifFalse:[
        setOfViews notNil ifTrue:[^ Array with:setOfViews]
                         ifFalse:[^ nil]
    ].
  ^ setOfViews select:[:aView|
        (setOfViews detect:[:v|aView isComponentOf:v] ifNone:nil) isNil
    ]
!

setDefaultActions
    "set default actions
    "
    pressAction      := [:pressPoint | self startSelectOrMove:pressPoint].
    shiftPressAction := [:pressPoint | self startSelectMoreOrMove:pressPoint].
    motionAction     := [:movePoint  | nil].
    releaseAction    := [nil].
    keyPressAction   := nil.

    self cursor:Cursor normal.

! !

!UIObjectView methodsFor:'object moving'!

doObjectMove:aPoint
    "move selection
    "
    movedObject notNil ifTrue:[
        self invertOutlineOf:movedObject.

        movedObject keysAndValuesDo:[:i :v|
            self moveObject:v to:(aPoint - (moveDelta at:i)).
        ].
        self invertOutlineOf:movedObject.
    ]

!

endObjectMove
    "cleanup after object(s) move
    "
    movedObject notNil ifTrue:[
        self invertOutlineOf:movedObject.

        movedObject size == 1 ifTrue:[
            movedObject := movedObject first
        ].
        self setSelection:movedObject withRedraw:true.
        movedObject := nil.
        self setDefaultActions.
        self layoutChanged.
    ].
!

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 withoutTransactionDo:[
            self shiftLayout:anObject top:dY bottom:dY left:dX right:dX
        ]
    ]

!

startObjectMoveAt:aPoint
    "start object(s) move at a point
    "
    self startObjectMove:(self selection) at:aPoint.
    movedObject := self selection.

    movedObject isCollection ifFalse:[
        movedObject := Array with:movedObject
    ].
    self setSelection:nil withRedraw:true.

    moveDelta := movedObject collect:[:aView|
        aPoint - aView computeOrigin
    ].
    self transaction:#move objects:movedObject do:[:v|self createUndoLayout:v].
    self invertOutlineOf:movedObject.
!

startSelectMoreOrMove:aPoint
    "add/remove to/from selection"

    |anObject|

    self enabled ifFalse:[^ 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; start moving or selection
    "
    |aView b v|

    self enabled ifFalse:[^ self].

    aView := self singleSelection.

    aView notNil ifTrue:[
        v := self findContainerOfView:aView.

        v specClass canResizeSubComponents ifTrue:[
            b := self whichHandleOf:aView isHitBy:aPoint.

            (b notNil and:[b ~~ #view]) ifTrue:[
                ^ self startResizeBorder:b of:aView.
            ]
        ].

        (self sensor ctrlDown and:[self canChangeLayoutOfView:aView]) ifFalse:[
            aView := nil
        ]
    ].

    aView isNil ifTrue:[
        (aView := self findObjectAt:aPoint) isNil ifTrue:[
            ^ self select:nil
        ].

        (self canChangeLayoutOfView:aView) ifFalse:[
            ^ self select:aView
        ]
    ].

    (self isSelected:aView) ifFalse:[
        self select:aView.
    ].

    (self numberOfSelections ~~ 1) ifTrue:[
        releaseAction := [
            self setDefaultActions.
            self select:aView
        ]
    ] ifFalse:[
        releaseAction := [self setDefaultActions]
    ].

    "prepare move operation for an object
    "

    motionAction := [:movePoint|
        (aPoint dist:movePoint) > 8.0 ifTrue:[
            self startObjectMoveAt:aPoint
        ]
    ].
! !

!UIObjectView methodsFor:'object resize'!

actionResize:anObject selector:aSelector
    "create and initialize action for resize
    "
    |selector delta|

    delta    := anObject container originRelativeTo:self.
    selector := ('resize:', aSelector, ':') asSymbol.

    resizeData := Structure with:(#object->anObject)
                            with:(#selector->selector)
                            with:(#delta->delta).

"can change cursor dependent on vertical/horizontal resizing
"
    oldCursor := cursor.
    self cursor:(Cursor leftHand).



!

doDragResize:aPoint
    "do a widget resize drag
    "
    |p object|

    object := resizeData object.

    self invertOutlineOf:object.
    p := (self alignToGrid:aPoint) - (resizeData delta).

    self perform:(resizeData selector) with:object with:p.
   "/ object geometryLayout:(object geometryLayout).
    self invertOutlineOf:object

!

endResize
    "cleanup after object resize
    "
    |object|

    object := resizeData object.
    resizeData := nil.

    self invertOutlineOf:object.
    self setDefaultActions.
    self elementChangedSize:object.

    "/ handle any expose events (for subcomponents) before
    "/ redrawing the handles.
    Delay waitForSeconds:0.05.
    [self sensor hasExposeEventFor:nil] whileTrue:[
        self windowGroup processExposeEvents
    ].

    self setSelection:object withRedraw:true.
    self layoutChanged.
!

startResizeBorder:b of:selection
    "resize selected view
    "
    |object|

    object := self singleSelection.
    self actionResize:object selector:b.

    self transaction:#resize selectionDo:[:aView|
        self createUndoLayout:aView
    ].
    self setSelection:nil withRedraw:true.

    motionAction  := [:movePoint | self doDragResize:movePoint].
    releaseAction := [self endResize].
    self invertOutlineOf:object
! !

!UIObjectView methodsFor:'private handles'!

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|

    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
    "show object unselected
    "
    |wasClipped r|

    selectionHiddenLevel ~~ 0 ifTrue:[^ self].

    (wasClipped := clipChildren) ifTrue:[
        self clippedByChildren:(clipChildren := false). 
    ].

    self handlesOf:aComponent do:[:rec :wht| self clearRectangle:rec ].

    wasClipped ifTrue:[
        self clippedByChildren:(clipChildren := true). 
    ].

    "/ must redraw all components which are affected b the handles

    r := (aComponent originRelativeTo:self) - (3@3) extent:(aComponent extent + (6@6)).

    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 shown ifTrue:[
                        v fill:v viewBackground.
                        v exposeX:0 y:0 width:9999 height:9999.
                    ]
                ]
            ]
        ]
    ]

    "Modified: 8.4.1997 / 00:32:26 / cg"
!

whichHandleOf:aComponent isHitBy:aPoint
    "returns kind of handle or nil
    "
    self handlesOf:aComponent do:[:rectangle :what|
        (rectangle containsPoint:aPoint) ifTrue:[^ what]
    ].
  ^ nil
! !

!UIObjectView methodsFor:'private resizing-subviews'!

resize:aView bottom:aPoint
    "resize a views bottom
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
    ]
!

resize:aView bottomLeft:aPoint
    "resize a views bottom and left
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:0
                            bottom:((aPoint y) - (aView computeCorner y))
                              left:((aPoint x) - (aView computeOrigin x))
                             right:0

    ]


!

resize:aView corner:aPoint
    "resize a views corner
    "
    |delta|

    delta := aPoint - aView computeCorner.

    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
    ]
!

resize:aView left:aPoint
    "resize a views left
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
    ]

!

resize:aView origin:aPoint
    "resize a views origin
    "
    |delta|

    delta := aPoint - aView computeOrigin.

    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
    ]

!

resize:aView right:aPoint
    "resize a views right
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
    ]
!

resize:aView top:aPoint
    "resize a views top
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y)) bottom:0
    ]
!

resize:aView topRight:aPoint
    "resize a views top and right
    "
    undoHistory withoutTransactionDo:[
        self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y))
                            bottom:0
                              left:0
                             right:((aPoint x) - (aView computeCorner x))

    ]

! !

!UIObjectView methodsFor:'private shift-layout'!

shiftLayout:aView left:l right:r
    "shift layout for a view; in case of an open transaction, the undo
     action is registered
    "
    self shiftLayout:aView top:0 bottom:0 left:l right:r

!

shiftLayout:aView top:t bottom:b
    "shift layout for a view; in case of an open transaction, the undo
     action is registered
    "
    self shiftLayout:aView top:t bottom:b left:0 right:0


!

shiftLayout:aView top:t bottom:b left:l right:r
    "shift layout for a view; in case of an open transaction, the undo
     action is registered
    "
    |type layout oldExt|

    type := self class layoutType:aView.

    type notNil ifTrue:[
        self createUndoLayout:aView.

        type == #Extent ifTrue:[
            oldExt := aView extent.
            aView extent:(oldExt + ((r-l) @ (b-t))).
            ^ self 
        ].

        layout := aView geometryLayout copy.

        layout isLayout ifTrue:[
            layout leftOffset:(layout leftOffset + l)
                    topOffset:(layout topOffset  + t).
                    
            type == #LayoutFrame ifTrue:[
                layout bottomOffset:(layout bottomOffset + b).
                layout  rightOffset:(layout rightOffset  + r).
            ]
        ] ifFalse:[
            type == #Rectangle ifTrue:[
                layout left:(layout left   + l)
                      right:(layout right  + r)
                        top:(layout top    + t)
                     bottom:(layout bottom + b).
            ] ifFalse:[     "POINT"
                layout x:(layout x + l) y:(layout y + t).
            ]
        ].
        aView geometryLayout:layout
    ]
! !

!UIObjectView methodsFor:'searching'!

findObjectAt:aPoint
    "find the origin/corner of the currentWidget
    "
    |view viewId lastId point listOfViews|

    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].

    "/ look for 'hidden' views ...

    listOfViews := OrderedCollection new.
    self allSubViewsDo:[:aView |
        |org|

        aView ~~ inputView ifTrue:[
            org := device translatePoint:0@0 from:(aView id) to:self id.
            ((org extent:aView extent) containsPoint:aPoint) ifTrue:[
                listOfViews add:aView.
            ]
        ]
    ].

    listOfViews size > 0 ifTrue:[
        ^ listOfViews last
    ].
    ^ nil


! !

!UIObjectView methodsFor:'selections'!

moveableSelection
    "checks whether the selection is not empty and all selected instances
     can be moved. If true the selection is returned otherwise nil
    "
    |coll|

    self hasSelection ifTrue:[
        (self canMove:(coll := self selection)) ifTrue:[
            ^ coll
        ]
    ].
  ^ nil
!

numberOfSelections
    "return the number of selected instances
    "
    |coll size|

    coll := self selection.
    size := coll size.

    (size ~~ 0 or:[coll isNil]) ifTrue:[^ size].
  ^ 1
!

selection:something
    "change selection to something
    "
    self select:something
!

selectionDo:aBlock
    "apply block to every selected object
    "
    self forEach:(self selection) do:aBlock


!

showSelection
    "show the selection - draw handles
    "
    selectionHiddenLevel == 0 ifTrue:[
        self selectionDo:[:el| self showSelected:el ]
    ].
!

singleSelection
    "checks whether one element is selected; in this case the element is
     returned otherwise nil
    "
    |coll|

    (coll := self selection) isCollection ifFalse:[
        ^ coll
    ].

    coll size == 1 ifTrue:[ ^ coll first].
  ^ nil
!

singleSelectionDo:aBlock
    "checks whether one element is selected; in this case the block
     with argument the selected instance will be processed
    "
    |view|

    (view := self singleSelection) notNil ifTrue:[
        aBlock value:view
    ]
!

unselect
    "clear selection
    "
    self select:nil
!

withSelectionHiddenDo:aBlock
    "apply block with selection hidden (no handles)
    "
    |coll|

    selectionHiddenLevel == 0 ifTrue:[
        self selectionDo:[:aView| self showUnselected:aView].
        device flush.
    ].
    selectionHiddenLevel := selectionHiddenLevel + 1.

    aBlock valueNowOrOnUnwindDo:[
        selectionHiddenLevel == 1 ifTrue:[
            setOfSuperViewsSizeChanged notEmpty ifTrue:[
                coll := self minSetOfSuperViews:setOfSuperViewsSizeChanged.
                coll do:[:aView| aView sizeChanged:nil].
                setOfSuperViewsSizeChanged := IdentitySet new
            ].
            selectionHiddenLevel := 0.
            self selectionDo:[:aView| self showSelected:aView].
        ] ifFalse:[
            selectionHiddenLevel := selectionHiddenLevel - 1.
        ]
    ]

!

withoutSelectionDo:aBlock
    "evaluate aBlock while selection is nilled
    "
    |sel|

    self hasSelection ifFalse:[
        aBlock value
    ] ifTrue:[
        sel := self selection.
        self setSelection:nil withRedraw:true.
        aBlock value.
        self setSelection:sel withRedraw:true.
    ]


! !

!UIObjectView methodsFor:'selections basic'!

selection
    "returns the current selection
    "
    ^ selection


!

setSelection:aNewSelection withRedraw:doRedraw
    "set a new selection without change notifications
    "
    |sel|

    (sel := aNewSelection) == self ifTrue:[
        sel := nil
    ].

    doRedraw ifTrue:[
        self hideSelection.
        selection := sel.
        self showSelection
    ] ifFalse:[
        selection := sel
    ]
! !

!UIObjectView methodsFor:'testing'!

hasSelection
    "returns true if any widget is selected
    "
    ^ self numberOfSelections ~~ 0

!

hasSingleSelection
    "returns true if one widget is selected
    "
    ^ self numberOfSelections == 1

!

hasUndoHistory
    "returns true if undos exists
    "
    ^ undoHistory isEmpty not
!

isModified
    "returns true if painter is modified
    "
  ^ undoHistory isModified
!

isSelected:anObject
    "return true, if the argument, anObject is selected
    "
    anObject notNil ifTrue:[
        self selectionDo:[:el| el == anObject ifTrue:[^ true]]
    ].
  ^ false

! !

!UIObjectView methodsFor:'transaction'!

createUndoLayout:aView
    "prepare undo action for a view changing its layout
    "
    self subclassResponsibility

!

transaction:aType objects:something do:aOneArgBlock
    "opens a transaction and evaluates a block within the transaction; the
     argument to the block is a view from derived from something
    "
    self subclassResponsibility


!

transaction:aType selectionDo:aOneArgBlock
    "opens a transaction and evaluates a block within the transaction; the
     argument to the block is a view from the selection
    "
    self transaction:aType objects:(self selection) do:aOneArgBlock


! !

!UIObjectView methodsFor:'user actions - dimension'!

copyExtent
    "copy the extent from the selected object
    "
    |object|

    object := self singleSelection.

    object notNil ifTrue:[
        copiedExtent := object computeExtent
    ] ifFalse:[
        self warn:'exactly one element must be selected'.
    ]



!

copyLayout
    "copy the layout from the selected object
    "
    |object|

    object := self singleSelection.

    object notNil ifTrue:[
        copiedLayout := object geometryLayout copy
    ] ifFalse:[
        self warn:'exactly one element must be selected'.
    ]



!

pasteExtent
    "paste the copied extent to all objects in the selection
    "
    copiedExtent notNil ifTrue:[
        self transaction:#pasteExtent dimensionDo:[:v|
            self resize:v corner:(v computeOrigin + copiedExtent)
        ]    
    ]    
!

pasteHeight
    "paste the copied extent height to all objects in the selection
    "
    copiedExtent notNil ifTrue:[
        self transaction:#pasteHeight dimensionDo:[:v|
            self resize:v bottom:(v computeOrigin + copiedExtent)
        ]    
    ]    

!

pasteLayout
    "paste layout to all objects in the selection
    "
    copiedLayout notNil ifTrue:[
        self transaction:#pasteLayout dimensionDo:[:v|
            v geometryLayout:(copiedLayout copy)
        ]    
    ]    
!

pasteWidth
    "paste the copied extent width to all objects in the selection
    "
    copiedExtent notNil ifTrue:[
        self transaction:#pasteWidth dimensionDo:[:v|
            self resize:v right:(v computeOrigin + copiedExtent)
        ]    
    ]    

!

setExtent:anExtent
    "change extent for all selected objects
    "
    self transaction:#extent dimensionDo:[:v|
        v geometryLayout:nil.
        v extent:anExtent.
    ].

    "Modified: 28.2.1997 / 12:49:00 / cg"
!

setLayout:aLayout
    "change layout for all selected objects
    "
    self transaction:#layout dimensionDo:[:v|
        v geometryLayout:(aLayout copy)
    ].    

!

setToDefaultExtent
    "change extent of all selected views to their default extent
    "
    self transaction:#defaultExtent dimensionDo:[:v|
        self resize:v corner:(v computeOrigin + (v preferredExtent)).
    ]    

!

setToDefaultHeight
    "change height of all selected views to their default height
    "
    self transaction:#defaultHeight dimensionDo:[:v|
        self resize:v bottom:(v computeOrigin + (v preferredExtent))
    ]    

!

setToDefaultWidth
    "change width of all selected views to their default width
    "
    self transaction:#defaultWidth dimensionDo:[:v|
        self resize:v right:(v computeOrigin + (v preferredExtent))
    ]    

!

transaction:aType dimensionDo:aOneArgBlock
    "change dimension within a transaction for the selected elements by evaluating
     the block with the argument a view.
    "
    self withSelectionHiddenDo:[
        self transaction:aType selectionDo:[:aView|
            (self class layoutType:aView) notNil ifTrue:[
                self createUndoLayout:aView.
                aOneArgBlock value:aView.
                self elementChangedSize:aView.
            ]
        ]
    ].
    self layoutChanged

! !

!UIObjectView methodsFor:'user actions - move'!

moveDo:aOneArgBlock
    "perform a move operation
    "
    |sensor tm|

    self moveableSelection isNil ifTrue:[
        ^ self
    ].
    sensor := self sensor.

    tm := 0.15.

    self withSelectionHiddenDo:[
        self transaction:#move selectionDo:[:aView|self createUndoLayout:aView].

        [
            self selectionDo:[:aView| aOneArgBlock value:aView ].
            Delay waitForSeconds:tm.
            tm := 0.02.
            self layoutChanged.
            sensor leftButtonPressed.
        ] whileTrue.

        "/ handle any expose events (for subcomponents) before
        "/ redrawing the handles.
        Delay waitForSeconds:0.05.
        [self sensor hasExposeEventFor:nil] whileTrue:[
            self windowGroup processExposeEvents
        ]
    ].
!

moveSelectionDown
    "move selection down
    "
    |gridY n|

    gridAlign notNil ifTrue:[gridY := gridAlign y]
                    ifFalse:[gridY := 1].

    self moveDo:[:aView|
        aligning ifTrue:[
            n := ((aView computeCorner y) \\ gridY).

            n ~~ 0 ifTrue:[
                n := gridY - n + 1.
            ] ifFalse:[
                n := gridY
            ]
        ] ifFalse:[
            n := 1
        ].
        self shiftLayout:aView top:n bottom:n
    ]
!

moveSelectionLeft
    "move selection left
    "
    |gridX n|

    gridAlign notNil ifTrue:[gridX := gridAlign x]
                    ifFalse:[gridX := 1].

    self moveDo:[:aView|
        aligning ifTrue:[
            n := ((aView computeOrigin x) \\ gridX).
            n == 0 ifTrue:[n := gridX].
            n := n negated.
        ] ifFalse:[
            n := -1
        ].
        self shiftLayout:aView left:n right:n
    ]
!

moveSelectionRight
    "move selection right
    "
    |gridX n|

    gridAlign notNil ifTrue:[gridX := gridAlign x]
                    ifFalse:[gridX := 1].

    self moveDo:[:aView|
        aligning ifTrue:[
            n := ((aView computeCorner x) \\ gridX).

            n ~~ 0 ifTrue:[n := n negated]
                  ifFalse:[n := gridX]
        ] ifFalse:[
            n := 1
        ].
        self shiftLayout:aView left:n right:n
    ]
!

moveSelectionUp
    "move selection up
    "
    |gridY n|

    gridAlign notNil ifTrue:[gridY := gridAlign y]
                    ifFalse:[gridY := 1].

    self moveDo:[:aView|
        aligning ifTrue:[
            n := ((aView computeOrigin x) \\ gridY).
            n == 0 ifTrue:[n := gridY].
            n := n negated.
        ] ifFalse:[
            n := -1
        ].
        self shiftLayout:aView top:n bottom:n
    ]

! !

!UIObjectView methodsFor:'user actions - position'!

alignSelectionBottom
    "align selection to the bottom of the first object in the selection; in case
     of one selection the object is aligned to the bottom of its superview
    "
    |bmost delta sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                bmost := (sel first) computeCorner y.

                self transaction:#alignBottom selectionDo:[:v|
                    (delta := bmost - (v computeCorner y)) ~~ 0 ifTrue:[
                        self shiftLayout:v top:delta bottom:delta.
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#Bottom do:[:aLayout|
                    aLayout bottomOffset:0.
                    aLayout bottomFraction:1.0
                ]
            ]
        ].
        self layoutChanged
    ]



!

alignSelectionCenterHor
    "align selection to the center/horizontal of the first object in the selection; in case
     of one selection the object is aligned to the center/horizontal of its superview
    "
    |view center sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            view := self singleSelection.

            view notNil ifTrue:[
                
                view   := self findContainerOfView:view.
                center := view computeExtent
            ] ifFalse:[
                view   := sel first.
                center := view computeCorner + view computeOrigin.
            ].
            center := center x // 2.

            self transaction:#alignCenterHorizontal selectionDo:[:v|
                |newX oldX delta|

                oldX  := v computeOrigin x.
                newX  := center - ((v computeCorner x - oldX) // 2).
                delta := newX - oldX.

                self shiftLayout:v left:delta right:delta
            ]
        ].
        self layoutChanged
    ]



!

alignSelectionCenterVer
    "align selection to the center/vertical of the first object in the selection; in case
     of one selection the object is aligned to the center/vertical of its superview
    "
    |view center sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            view := self singleSelection.

            view notNil ifTrue:[
                view   := self findContainerOfView:view.
                center := view computeExtent
            ] ifFalse:[
                view   := sel first.
                center := view computeCorner + view computeOrigin.
            ].
            center := center y // 2.

            self transaction:#alignCenterVertical selectionDo:[:v|
                |newY oldY delta|

                oldY  := v computeOrigin y.
                newY  := center - ((v computeCorner y - oldY) // 2).
                delta := newY - oldY.

                self shiftLayout:v top:delta bottom:delta
            ]
        ].
        self layoutChanged
    ]
!

alignSelectionLeft
    "align selection to the left of the first object in the selection; in case
     of one selection the object is aligned to the left of its superview
    "
    |lmost delta sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                lmost := (sel first) computeOrigin x.

                self transaction:#alignLeft selectionDo:[:v|
                    (delta := lmost - (v computeOrigin x)) ~~ 0 ifTrue:[
                        self shiftLayout:v left:delta right:delta
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#Left do:[:aLayout|
                    aLayout leftOffset:0.
                    aLayout leftFraction:0.0.
                ]
            ]
        ].
        self layoutChanged
    ]
!

alignSelectionLeftAndRight
    "align selection to the left/right of the first object in the selection; in case
     of one selection the object is aligned to the left/right of its superview
    "
    |lmost rmost sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                lmost := (sel first) computeOrigin x.
                rmost := (sel first) computeCorner x.

                self transaction:#alignLeftRight selectionDo:[:aView|
                    |layout|
                    layout := self class asLayoutFrameFromView:aView.

                    layout notNil ifTrue:[
                        self createUndoLayout:aView.
                        aView geometryLayout:layout.

                        undoHistory withoutTransactionDo:[    
                            self shiftLayout:aView left:(lmost - (aView computeOrigin x))
                                                  right:(rmost - (aView computeCorner x)).
                        ].
                        self elementChangedSize:aView
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#LeftRight do:[:aLayout|
                    aLayout leftOffset:0.
                    aLayout leftFraction:0.0.
                    aLayout rightOffset:0.
                    aLayout rightFraction:1.0.
                ]
            ]
        ].
        self layoutChanged
    ].

!

alignSelectionRight
    "align selection to the right of the first object in the selection; in case
     of one selection the object is aligned to the right of its superview
    "
    |rmost delta sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                rmost := (sel first) computeCorner x.

                self transaction:#alignRight selectionDo:[:v|
                    (delta := rmost - (v computeCorner x)) ~~ 0 ifTrue:[
                        self shiftLayout:v left:delta right:delta
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#Right do:[:aLayout|
                    aLayout rightOffset:0.
                    aLayout rightFraction:1.0.
                ]
            ]
        ].
        self layoutChanged
    ]
!

alignSelectionTop
    "align selection to the top of the first object in the selection; in case
     of one selection the object is aligned to the top of its superview
    "
    |tmost delta sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                tmost := (sel first) computeOrigin y.

                self transaction:#alignTop selectionDo:[:v|
                    (delta := tmost - (v computeOrigin y)) ~~ 0 ifTrue:[
                        self shiftLayout:v top:delta bottom:delta
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#Top do:[:aLayout|
                    aLayout topOffset:0.
                    aLayout topFraction:0.0.
                ]
            ]
        ].
        self layoutChanged
    ]

!

alignSelectionTopAndBottom
    "align selection to the top/bottom of the first object in the selection; in case
     of one selection the object is aligned to the top/bottom of its superview
    "
    |tmost bmost sel|

    (sel := self moveableSelection) notNil ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                tmost := (sel first) computeOrigin y.
                bmost := (sel first) computeCorner y.

                self transaction:#alignTopBottom selectionDo:[:aView|
                    |layout|
                    layout := self class asLayoutFrameFromView:aView.

                    layout notNil ifTrue:[
                        self createUndoLayout:aView.
                        aView geometryLayout:layout.

                        undoHistory withoutTransactionDo:[    
                            self shiftLayout:aView top:(tmost - (aView computeOrigin y))
                                                bottom:(bmost - (aView computeCorner y)).
                        ].
                        self elementChangedSize:aView
                    ]
                ]
            ] ifFalse:[
                self extentToFrame:#TopBottom do:[:aLayout|
                    aLayout topOffset:0.
                    aLayout topFraction:0.0.
                    aLayout bottomOffset:0.
                    aLayout bottomFraction:1.0.
                ]
            ]
        ].
        self layoutChanged
    ]
!

centerSelection:aOneArgBlockXorY orientation:orientation
    "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 moveableSelection) isNil ifTrue:[
        ^ self
    ].

    self withSelectionHiddenDo:[
        max := 0.

        self selectionDo:[:aView |
            superview isNil ifTrue:[
                superview := self findContainerOfView:aView
            ] ifFalse:[
                (self findContainerOfView:aView) == 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:[
            |type|
            (orientation == #y) ifTrue:[type := #centerVertical]
                               ifFalse:[type := #centerHorizontal].
            delta := max - min.

            self transaction:type selectionDo:[:v|
                orientation == #y ifTrue:[
                    self shiftLayout:v top:delta bottom:delta
                ] ifFalse:[
                    self shiftLayout:v left:delta right:delta
                ]
            ]
        ].
        self layoutChanged
    ]


!

centerSelectionHor
    "center selection horizontal
    "
    self centerSelection:[:aPoint| aPoint x] orientation:#x


!

centerSelectionVer
    "center selection vertical
    "
    self centerSelection:[:aPoint| aPoint y] orientation:#y
!

extentToFrame:toWhat do:aBlock
    "align to frame (Left Right ...) and perform the block on a frameLayout
    "
    |layout type|

    type := ('extent', toWhat asString) asSymbol.

    self transaction:type selectionDo:[:aView|
        layout := self class asLayoutFrameFromView:aView.

        layout notNil ifTrue:[
            self createUndoLayout:aView.
            aBlock value:layout.
            aView geometryLayout:layout.
            self elementChangedSize:aView.
        ]
    ]
!

spreadSelectionHor
    "spread multiple selection horizontal
    "
    |sumWidths min max viewsInOrder topsInOrder count space sel|

    sel := self moveableSelection.

    (sel notNil and:[self numberOfSelections > 1]) ifFalse:[
        ^ self
    ].

    self withSelectionHiddenDo:[
        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:sel.
        topsInOrder  := viewsInOrder collect:[:aView | aView left].
        topsInOrder sortWith:viewsInOrder.

        space := (((max - min) - sumWidths) / (count - 1)) rounded asInteger.

        self transaction:#spreadHorizontal objects:viewsInOrder do:[:aView|
            |delta|

            delta := min - aView computeOrigin x.
            self shiftLayout:aView left:delta right:delta.
            min := min + aView computeExtent x + space
        ]
    ].
    self layoutChanged

!

spreadSelectionVer
    "spread multiple selection vertical
    "
    |sumHeights min max viewsInOrder topsInOrder count space sel|

    sel := self moveableSelection.

    (sel notNil and:[self numberOfSelections > 1]) ifFalse:[
        ^ self
    ].

    self withSelectionHiddenDo:[
        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:sel.
        topsInOrder  := viewsInOrder collect:[:aView|aView top].
        topsInOrder sortWith:viewsInOrder.

        space := (((max - min) - sumHeights) / (count - 1)) rounded asInteger.

        self transaction:#spreadVertical objects:viewsInOrder do:[:aView|
            |delta|

            delta := min - aView computeOrigin y.
            self shiftLayout:aView top:delta bottom:delta.
            min := min + aView height + space
        ]
    ].
    self layoutChanged
! !

!UIObjectView methodsFor:'user actions - undo history'!

enableUndoHistory:aState
    "enable or disable undo history
    "
    undoHistory enabled:aState
!

openUndoMenu
    "open undo menu
    "
    self select:nil.
    undoHistory openUndoMenu
!

removeUndoHistory
    "delete total undo history
    "
    undoHistory on:self
!

undoLast
    "undo last action
    "
    |newSel oldSel|

    undoHistory isEmpty ifFalse:[
        self hasSelection ifTrue:[
            oldSel := OrderedCollection new.
            newSel := OrderedCollection new.

            self selectionDo:[:aView||p|
                (p := self propertyOfView:aView) notNil ifTrue:[
                    oldSel add:(p identifier)
                ]
            ].
            self setSelection:nil withRedraw:true.
        ].

        self withSelectionHiddenDo:[undoHistory undoLast:1].

        oldSel notNil ifTrue:[
            oldSel do:[:id||v|
                (v := self findViewWithId:id) notNil ifTrue:[newSel add:v]
            ].
            self select:newSel.
        ]
    ].
! !

!UIObjectView::UndoHistory class methodsFor:'constants'!

maxHistorySize
    "returns maximum size of history before removing oldest
     record
    "
    ^ 100


! !

!UIObjectView::UndoHistory class methodsFor:'documentation'!

documentation
"
    undo history used by the UIPainter-Tool; to each operation, an undo block
    and some text is stored. In case of a required undo, the corresponding
    undo block will be performed.

    [see also:]
        UIObjectView
        UIPainterView

    [author:]
        Claus Atzkern
"


! !

!UIObjectView::UndoHistory class methodsFor:'instance creation'!

on:aPainter
    |history|

    history := self new.
    history on:aPainter.
  ^ history


! !

!UIObjectView::UndoHistory methodsFor:'accessing'!

addUndoSelector:aSelector withArgs:anArray
    "add a selector with arguments to the current opened transaction; in case that no
     transaction is opened or disabled the block will not be kept in the history.
    "
    self isTransactionOpen ifTrue:[
        transaction add:(Association key:aSelector value:anArray)
    ]


! !

!UIObjectView::UndoHistory methodsFor:'accessing behavior'!

enabled
    ^ enabled
!

enabled:aState
    enabled := aState
!

resetModification
    "set modification state to false
    "
    startIdentifier := identifier
! !

!UIObjectView::UndoHistory methodsFor:'activation'!

withinTransaction:aType text:aTextOrNil do:aBlock
    "open a transaction; perform the block; at least close the transaction
    "
    (enabled and:[transaction isNil]) ifTrue:[
        transaction := Transaction type:aType text:aTextOrNil.

        aBlock value.

        transaction isEmpty ifFalse:[
            identifier := identifier + 1.
            transaction identifier:identifier.
            history addLast:transaction.
            history size > (self class maxHistorySize) ifTrue:[history removeFirst]
        ].
        transaction := nil

    ] ifFalse:[
        aBlock value
    ]
!

withoutTransactionDo:aNoneArgBlock
    "evaluate the block without opening a transaction or keeping changes
     within a still opened transaction
    "
    |oldState|

    oldState := enabled.
    enabled  := false.
    aNoneArgBlock value.
    enabled  := oldState.
! !

!UIObjectView::UndoHistory methodsFor:'initialization'!

on:aPainter
    "setup for a painter and delete all existing history records
    "
    identifier      := 0.
    startIdentifier := 0.

    painter     := aPainter.
    history     := OrderedCollection new.
    transaction := nil.
    enabled     := true.


! !

!UIObjectView::UndoHistory methodsFor:'menu'!

openUndoMenu
    |list tabs top slv hzp inset selection okButton|

    history isEmpty ifTrue:[
        ^ self
    ].

    top  := StandardSystemView new label:'undo history'; extent:250@350.
    slv  := ScrollableView for:SelectionInListView origin:0.0@0.0 corner:1.0@1.0 in:top.
    hzp  := HorizontalPanelView origin:0.0@1.0 corner:1.0@1.0 in:top.
    hzp horizontalLayout:#fitSpace.

    (Button abortButtonIn:hzp) action:[ selection := nil. top destroy ].
    okButton := Button okButtonIn:hzp.
    okButton label:'undo to end'.
    okButton action:[ top destroy ].

    inset := hzp preferredExtent y.
    hzp topInset:(inset negated).
    slv   bottomInset:inset.
    slv := slv scrolledView.

    tabs := TabulatorSpecification new.
    tabs unit:#cm.
    tabs positions:#(0 5).
    tabs align:#(#left #left).

    list := history collect:[:aTrans||e|
        e := MultiColListEntry new.
        e colAt:1 put:(aTrans typeAsString).
        e colAt:2 put:(aTrans text ? '').
        e tabulatorSpecification:tabs.
        e
    ].

    slv list:list.
    slv action:[:index | selection := index ].
    top openModal.

    selection notNil ifTrue:[
        self undoLast:(history size - selection + 1).
    ]
! !

!UIObjectView::UndoHistory methodsFor:'testing'!

isEmpty
    "returns true if undo history is empty
    "
    ^ history isEmpty


!

isModified
    "returns true if history is modified
    "
    self isEmpty ifTrue:[
        ^ false
    ].
  ^ history last identifier ~~ startIdentifier
!

isTransactionOpen
    ^ (enabled and:[transaction notNil])
! !

!UIObjectView::UndoHistory methodsFor:'undo'!

undoLast:nTransactions
    "undo last n transactions; an open transaction will be closed;
     transactions during undo are disabled
    "
    |repeatTimes transaction actions|

    transaction := nil.
    enabled     := false.
    repeatTimes := nTransactions min:(history size).

    repeatTimes timesRepeat:[
        transaction := history removeLast.
        actions     := transaction actions.

        actions isCollection ifTrue:[
            actions reverseDo:[:aBlock|
                painter perform:(aBlock key) with:(aBlock value)
            ]
        ] ifFalse:[
            painter perform:(actions key) with:(actions value)
        ]
    ].
    enabled := true.
! !

!UIObjectView::UndoHistory::Transaction class methodsFor:'documentation'!

documentation
"
    represents one undo record, keeping the associated type and printable text
    and the undo action performed on an undo request

    [see also:]
        UndoHistory

    [author:]
        Claus Atzkern
"

! !

!UIObjectView::UndoHistory::Transaction class methodsFor:'instance creation'!

type:aType text:aTextOrNil
    ^ self new type:aType text:aTextOrNil


! !

!UIObjectView::UndoHistory::Transaction methodsFor:'accessing'!

actions
    "returns actions associated with transaction
    "
  ^ actions
!

identifier
    "gets my identifier
    "
  ^ identifier
!

identifier:anIdentifier
    "sets my identifier
    "
    identifier := anIdentifier
!

text
    "returns text or nil assigned to transaction
    "
    ^ text
!

type
    "returns type assigned to transaction
    "
    ^ type
!

type:aType
    "change type assigned to transaction
    "
    type := aType
!

typeAsString
    "returns type as printable string
    "
    |line name size sep|

    line := type asString.
    size := 0.
    line do:[:c| (c isUppercase) ifTrue:[size := size+1] ].
    name := String new:(line size + size).
    size := 1.
    sep  := Character space.

    line do:[:c|
        (c isUppercase) ifFalse:[
            name at:size put:c
        ] ifTrue:[
            name at:size put:sep.
            sep  := $&.
            size := size + 1.
            name at:size put:(c asLowercase)
        ].
        size := size + 1
    ].
    ^ name
! !

!UIObjectView::UndoHistory::Transaction methodsFor:'adding'!

add:anUndoBlock
    "add an undo action to the current transaction
    "
    actions isNil ifTrue:[
        actions := anUndoBlock
    ] ifFalse:[
        actions isCollection ifFalse:[
            actions := OrderedCollection with:actions
        ].
        actions add:anUndoBlock.
    ]
! !

!UIObjectView::UndoHistory::Transaction methodsFor:'initialization'!

type:aType text:aTextOrNil
    "initialize transaction
    "
    type := aType.
    text := aTextOrNil.
! !

!UIObjectView::UndoHistory::Transaction methodsFor:'testing'!

isEmpty
    "returns true if no undo action is registered
    "
    ^ actions isNil
! !

!UIObjectView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !