UIObjectView.st
author Claus Gittinger <cg@exept.de>
Fri, 28 Feb 1997 13:25:51 +0100
changeset 67 09e9d4b57142
parent 63 6714daee4b26
child 68 889c3877baf0
permissions -rw-r--r--
alignmentLayout

ObjectView subclass:#UIObjectView
	instanceVariableNames:'inputView testMode undoHistory copiedExtent actionData
		createClass clipChildren selectionHiddenLevel
		setOfSuperViewsSizeChanged'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

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

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


!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 layout|

    (layout := aView geometryLayout) isNil ifTrue:[
        ^ nil
    ].

    layout isLayout ifTrue:[
        layout isLayoutFrame ifTrue:[^ layout copy].

        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.
    ] ifFalse:[
        lF := rF := tF := bF := 0.

        layout isRectangle ifTrue:[
            lO := layout left.
            tO := layout top.
            rO := layout right.
            bO := layout bottom.
        ] ifFalse:[
            layout isPoint ifFalse:[ ^ nil ].

            lO := layout x.
            tO := layout y.
            rO := lO + aView extent x.
            bO := tO + aView extent y.
        ].
    ].

    ^ LayoutFrame leftFraction:lF offset:lO  rightFraction:rF offset:rO
                   topFraction:tF offset:tO bottomFraction:bF offset:bO
! !

!UIObjectView class methodsFor:'defaults'!

defaultGrid
    ^ 4 @ 4

!

gridShown
    ^ false

!

handleSize
    "size of blob drawn for handles"
    ^ 4

!

hitDelta
    ^ 4

! !

!UIObjectView class methodsFor:'queries'!

layoutType:aView
    "returns layout type of aView or nil
    "
    |layout spec|

    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:[
        spec := aView superView specClass.

        spec canResizeSubComponents     ifTrue:[ ^ #Extent ].
    ].
    ^ nil

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

!UIObjectView methodsFor:'accessing'!

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

testMode
    "returns true if running test
    "
    ^ testMode


!

testMode:aBoolean
    "change test mode
    "
    (aBoolean == testMode) ifFalse:[
        testMode := aBoolean.

        testMode ifTrue:[
            self unselect.
            inputView unrealize
        ] ifFalse:[
            inputView raise.
            inputView realize
        ]
    ]


! !

!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

! !

!UIObjectView methodsFor:'event handling'!

elementChangedSize:aView
    "some element has changed its size; collect them during selectionHiddenLevel 
     is on
    "
    selectionHiddenLevel ~~ 0 ifTrue:[
        setOfSuperViewsSizeChanged add:aView superView
    ] ifFalse:[
        aView superView sizeChanged:nil
    ]
!

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.
"/    selectionHiddenLevel == 0 ifTrue:[
        self selectionDo:[:v | self showSelected:v]
"/    ]

!

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

    key == #InspectIt ifTrue:[
        ^ self inspectSelection
    ].

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

    super keyPress:key x:x y:y


!

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
    "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 new.
    testMode     := false.
    clipChildren := true.
    selectionHiddenLevel := 0.

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

!

realize
    super realize.
    self windowGroup postEventHook:self

! !

!UIObjectView methodsFor:'misc'!

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


!

invertOutlineOf:anObject
    "invert outline of an object
    "
    |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
    "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 creation'!

actionCreate:anObject frame:aFrame delta:aDelta
    "create and initialize action data
    "
    |extent x y selectors values|

"minimum extent
"
    extent := self extent.
    x := extent x // 3.
    y := extent y // 3.
    extent := anObject preferredExtent.

    (extent x > x) ifTrue:[extent x:x].
    (extent y > y) ifTrue:[extent y:y].

"setup structure
"
    selectors := #( object frame delta vertical horizontal minExtent ).
    values    := Array new:(selectors size).

    values at:1 put:anObject.
    values at:2 put:aFrame.
    values at:3 put:aDelta.
    values at:4 put:(self isVerticalResizable:anObject).
    values at:5 put:(self isHorizontalResizable:anObject).
    values at:6 put:extent.

    actionData := Structure newWith:selectors values:values.


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



!

createWidgetWithClass:aClass
    "prepare to create new widgets
    "
    createClass := aClass.
    pressAction := [:pressPoint | self startCreate:pressPoint].
    self cursor:Cursor origin.


!

doDragCreate:aPoint
    "do a widget create drag
    "
    |frame object extent minimum|

    frame   := actionData frame.
    frame corner:((self alignToGrid:aPoint) - (actionData delta)).

    object  := actionData object.
    minimum := actionData minExtent.
    extent  := frame extent.

    ((extent x < minimum x) or:[actionData horizontal not]) ifTrue:[
        extent x:(minimum x)
    ].

    ((extent y < minimum y) or:[actionData vertical not]) ifTrue:[
        extent y:(minimum y)
    ].

    frame extent:extent.

    self invertOutlineOf:object.
    object origin:(frame origin) extent:(frame extent).
    self invertOutlineOf:object.
!

endCreate
    "end a widget create drag
    "
    |layout x y object|

    object := actionData object.
    self invertOutlineOf:object.
    inputView raise.

    object superView specClass basicNew setupInitialLayoutFor:object.

    self changed:#tree.
    self select:object.
    actionData := nil.

    self setDefaultActions.

!

setupCreatedObject:anObject
    self subclassResponsibility
!

startCreate:aPoint
    "start a widget create
    "
    |widget object start frame delta|

    (createClass isNil or:[self numberOfSelections > 1]) ifTrue:[
        self unselect.
      ^ self setDefaultActions.
    ].

    (widget := self singleSelection) notNil ifTrue:[
        self unselect.

        (self isPoint:aPoint containedIn:widget) ifFalse:[
            widget := self
        ] ifTrue:[
            widget specClass supportsSubComponents ifFalse:[
                ^ self setDefaultActions.
            ]
        ]
    ] ifFalse:[
        widget := self
    ].

    motionAction  := [:movePoint| self doDragCreate:movePoint].
    releaseAction := [ self endCreate].

    object := createClass new.
    widget addSubView:object.

    start := self alignToGrid:aPoint.
    delta := widget originRelativeTo:self.
    frame := Rectangle origin:(start - delta) corner:start.

    object origin:(frame origin).
    self setupCreatedObject:object.
    object realize.

    self actionCreate:object frame:frame delta:delta.
    self invertOutlineOf:object.


! !

!UIObjectView methodsFor:'object moving'!

doObjectMove:aPoint
    "move selection
    "
    movedObject notNil ifTrue:[
        movedObject keysAndValuesDo:[:nr :aView|
            self invertOutlineOf:aView.
            self moveObject:aView to:(aPoint - (moveDelta at:nr)).
            self invertOutlineOf:aView.
        ]
    ]

!

endObjectMove
    "cleanup after object(s) 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.
    ].
!

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

!

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

    selection isCollection ifTrue:[
        movedObject := selection
    ] ifFalse:[
        movedObject := Array with:selection
    ].
    super unselect.

    moveDelta := movedObject collect:[:aView|
        aPoint - aView computeOrigin
    ].

    self transaction:#move objects:movedObject do:[:aView|
        self invertOutlineOf:aView.
        self undoLayoutView: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; start moving or selection
    "
    |aView b|

    testMode ifTrue:[^ self].

    aView := self singleSelection.

    aView notNil ifTrue:[
        (aView superView specClass canResizeSubComponents) ifTrue:[
            b := self whichHandleOf:aView isHitBy:aPoint.

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

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

    (self canMove:aView) ifFalse:[
        super unselect.
      ^ self select:aView
    ].

    (self isSelected:aView) ifFalse:[
        super unselect.
        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) > 4.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.

    actionData := 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 := actionData object.

    self invertOutlineOf:object.
    p := (self alignToGrid:aPoint) - (actionData delta).
    self perform:(actionData selector) with:object with:p.
    object geometryLayout:(object geometryLayout).
    self invertOutlineOf:object

!

endResize
    "cleanup after object resize
    "
    |object|

    object := actionData object.
    actionData := nil.

    self invertOutlineOf:object.
    self setDefaultActions.
    self elementChangedSize:object.
    super select:object.
    self changed:#layout.
!

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

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

    self transaction:#extent selectionDo:[:aView|
        self undoLayoutView:aView
    ].
    super unselect.

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

!UIObjectView methodsFor:'private handles'!

handlesOf:aView do:aBlock
    |dlta type v h|

    dlta := (aView originRelativeTo:self) - aView origin.
    type := self class layoutType:aView.

    (type == #LayoutFrame or:[type == #Rectangle]) ifTrue:[
        v := self isVerticalResizable:aView.
        h := self isHorizontalResizable:aView.

        h ifTrue:[  aBlock value:(aView leftCenter   + dlta) value:#left.
                    aBlock value:(aView rightCenter  + dlta) value:#right.
                 ].
        v ifTrue:[  aBlock value:(aView topCenter    + dlta) value:#top.
                    aBlock value:(aView bottomCenter + dlta) value:#bottom.
                 ].

        (h and:[v]) ifTrue:[
            aBlock value:(aView origin     + dlta) value:#origin.
            aBlock value:(aView topRight   + dlta) value:#topRight.
            aBlock value:(aView bottomLeft + dlta) value:#bottomLeft.
            aBlock value:(aView corner     + dlta) value:#corner.
          ^ self
        ]
    ].

    aBlock value:(aView origin     + dlta) value:#view.
    aBlock value:(aView topRight   + dlta) value:#view.
    aBlock value:(aView bottomLeft + dlta) value:#view.

    type == #Extent ifTrue:[
        v := self isVerticalResizable:aView.
        h := self isHorizontalResizable:aView.

        v ifTrue:[aBlock value:(aView bottomCenter + dlta) value:#bottom].
        h ifTrue:[aBlock value:(aView rightCenter  + dlta) value:#right ].

        (h and:[v]) ifTrue:[
            aBlock value:(aView corner + dlta) value:#corner.
          ^ self
        ]
    ].
    aBlock value:(aView corner + dlta) value:#view.
!

showSelected:aComponent
    "show object selected
    "
    |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
    "show object unselected
    "
    |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
    "returns kind of handle or nil
    "
    |bounds|

    self handlesOf:aView do:[:pnt :what |
        ((pnt - (4@4) extent:7@7) containsPoint:aPoint) ifTrue:[
            ^ what
        ].
    ].

    ^ nil

    "Modified: 5.9.1995 / 14:39:34 / claus"

! !

!UIObjectView methodsFor:'private resizing-subviews'!

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

resize:aView bottomLeft:aPoint
    "resize a views bottom and left
    "
    undoHistory disabledTransitionDo:[
        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 disabledTransitionDo:[
        self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
    ]
!

resize:aView left:aPoint
    "resize a views left
    "
    undoHistory disabledTransitionDo:[
        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 disabledTransitionDo:[
        self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
    ]

!

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

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

resize:aView topRight:aPoint
    "resize a views top and right
    "
    undoHistory disabledTransitionDo:[
        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|

    type := self class layoutType:aView.

    type notNil ifTrue:[
        self undoLayoutView:aView.

        type == #Extent ifTrue:[
            ^ aView geometryLayout:layout
        ].

        layout := aView geometryLayout.

        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


!

isPoint:aPoint containedIn:aView
    "checks whether a point is covered by a view.
    "
    |p|

    p := device translatePoint:aPoint from:inputView id to:aView id.

    (p x >= 0 and:[p y >= 0]) ifTrue:[
        p := aView extent - p.

        (p x >= 0 and:[p y >= 0]) ifTrue:[
            ^ true
        ]
    ].
    ^ false
!

whichBorderOf:aView isHitBy:aPoint
    |p r bw org|

    bw := aView borderWidth.
    p := aPoint - (aView superView originRelativeTo:self).

    r := Rectangle origin:(aView origin)
                   extent:(aView width @ bw).
    (r containsPoint:p) ifTrue:[^ #top:].

    r origin:(aView left @ (aView bottom + bw)) extent:(aView width @ bw).
    (r containsPoint:p) ifTrue:[^ #bottom:].

    r top:(aView top).
    r extent:(bw @ aView height).
    (r containsPoint:p) ifTrue:[^ #left:].

    r origin:((aView right + bw) @ aView top).
    (r containsPoint:p) ifTrue:[^ #right:].

    ^ nil


! !

!UIObjectView methodsFor:'selections'!

addToSelection:something
    "add something to selection
    "
    (self canSelect:something) ifTrue:[
        super addToSelection:something.
        self changed:#selection.
    ]
!

inspectSelection
    "inspect selection
    "
    self singleSelectionDo:[:aView |
        aView inspect
    ]
!

numberOfSelections
    "return the number of selected entries
    "
    |sz|

    selection isNil ifTrue:[^ 0].

    selection isCollection ifTrue:[^ selection size]
                          ifFalse:[^ 1 ]
!

removeFromSelection:something
    "remove something from selection
    "
    super removeFromSelection:something.
    self changed:#selection

!

select:something
    "change selection to something
    "
    (self canSelect:something) ifTrue:[
        super select:something.
        self changed:#selection
    ]

!

selection
    "returns selection
    "
    ^ selection


!

showSelection
    selectionHiddenLevel == 0 ifTrue:[
        super showSelection.
    ].
!

singleSelection
    "returns single selection or nil
    "
    selection isCollection ifFalse:[
        ^ selection
    ].
    selection size == 1 ifTrue:[ ^ selection at:1]
                       ifFalse:[ ^ nil].
!

singleSelectionDo:aBlock
    "perform block with argument a view in case of one selection
    "
    |view|

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

unselect
    "clear selection
    "
    selection notNil ifTrue:[
        super unselect.
        self changed:#selection
    ]

!

withSelectionHiddenDo:aBlock
    "apply block with selection hidden (no handles)
    "
    selectionHiddenLevel := selectionHiddenLevel + 1.

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

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

!

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

    selection isNil ifTrue:[
        aBlock value
    ] ifFalse:[
        sel := selection.
        super unselect.
        aBlock value.
        super select:sel
    ]


! !

!UIObjectView methodsFor:'testing'!

canMove:something
    "returns always true; all contained views can be moved
    "
    |sv|

    something notNil ifTrue:[
        self forEach:something do:[:v|
            sv ~~ v superView ifTrue:[
                (sv notNil or:[v superView specClass isLayoutContainer]) ifTrue:[
                    ^ false
                ].
                sv := v superView
            ]
        ].
        ^ true
    ].
    ^ false

!

canPaste:something
    "returns true if something could be paste
    "
    something notNil ifTrue:[
        something isCollection ifTrue:[
            something notEmpty ifTrue:[
                ^ (something at:1) isKindOf:UISpecification
            ]
        ] ifFalse:[
            ^ something isKindOf:UISpecification
        ]
    ].
    ^ false

!

canPasteInto:something
    "can paste into something ?
    "
    something notNil ifTrue:[
        something isCollection ifFalse:[
            ^ something specClass supportsSubComponents
        ].
        something size == 1 ifTrue:[
            ^ (something at:1) specClass supportsSubComponents
        ]
    ].
    ^ false
!

canSelect:something
    "returns true if something can be selected and testMode is disabled
    "
    ^ (testMode not and:[something ~~ selection])

!

hasUndos
    "returns true if undoHistory not empty
    "
    ^ undoHistory notEmpty
!

isHorizontalResizable:aComponent
    "returns true if instance is horizontal resizeable
    "
    ^ self subclassResponsibility


!

isVerticalResizable:aComponent
    "returns true if instance is vertical resizeable
    "
    ^ self subclassResponsibility


! !

!UIObjectView methodsFor:'transaction'!

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:selection do:aOneArgBlock


!

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

! !

!UIObjectView methodsFor:'user actions - arrange'!

lowerSelection
    "lower all objects in the selection
    "
    self selectionDo:[:aView| aView lower ].


!

raiseSelection
    "raise all objects in the selection
    "
    self selectionDo:[:aView| aView raise ].
    inputView raise.


! !

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



!

pasteExtent
    "paste the copied extent to all objects in the selection
    "
    copiedExtent notNil ifTrue:[
        self transition:#extent 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 transition:'paste height' dimensionDo:[:v|
            self resize:v bottom:(v computeOrigin + copiedExtent)
        ]    
    ]    

!

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

!

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

!

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

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

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

!

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

!

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

!

transition: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 undoLayoutView:aView.
                aOneArgBlock value:aView.
                self elementChangedSize:aView.
            ]
        ]
    ].
    self changed:#layout

! !

!UIObjectView methodsFor:'user actions - move'!

moveSelectionDown:aNumber
    "move selection down
    "
    |gridY|

    (self canMove:selection) ifTrue:[
        gridAlign notNil ifTrue:[gridY := gridAlign y].

        self withSelectionHiddenDo:[
            self transaction:#move selectionDo:[:aView|
                |n d|

                n := aNumber.

                aligning ifTrue:[
                    d := ((aView computeCorner y) \\ gridY).
                    n := n * gridY.

                    d ~~ 0 ifTrue:[
                        n := n - d + 1.
                    ]
                ].
                self shiftLayout:aView top:n bottom:n
            ]
        ].
        self changed:#layout
    ]

!

moveSelectionLeft:aNumber
    "move selection left
    "
    |gridX|

    (self canMove:selection) ifTrue:[
        gridAlign notNil ifTrue:[gridX := gridAlign x].

        self withSelectionHiddenDo:[
            self transaction:#move selectionDo:[:aView|
                |n d|

                n := aNumber.

                aligning ifTrue:[
                    d := ((aView computeOrigin x) \\ gridX).
                    d ~~ 0 ifTrue:[
                        n := n-1.
                    ].
                    n := (n * gridX) + d.
                ].
                n := n negated.
                self shiftLayout:aView left:n right:n
            ]
        ].
        self changed:#layout
    ]
!

moveSelectionRight:aNumber
    "move selection right
    "
    |gridX|

    (self canMove:selection) ifTrue:[
        gridAlign notNil ifTrue:[gridX := gridAlign x].

        self withSelectionHiddenDo:[
            self transaction:#move selectionDo:[:aView|
                |n d|

                n := aNumber.

                aligning ifTrue:[
                    d := ((aView computeCorner x) \\ gridX).
                    n := n * gridX.

                    d ~~ 0 ifTrue:[
                        n := n - d + 1.
                    ]
                ].
                self shiftLayout:aView left:n right:n
            ]
        ].
        self changed:#layout
    ]
!

moveSelectionUp:aNumber
    "move selection up
    "
    |gridY|

    (self canMove:selection) ifTrue:[
        gridAlign notNil ifTrue:[gridY := gridAlign y].

        self withSelectionHiddenDo:[
            self transaction:#move selectionDo:[:aView|
                |n d|

                n := aNumber.

                aligning ifTrue:[
                    d := ((aView computeOrigin x) \\ gridY).
                    d ~~ 0 ifTrue:[
                        n := n-1.
                    ].
                    n := (n * gridY) + d.
                ].
                n := n negated.
                self shiftLayout:aView top:n bottom:n
            ]
        ].
        self changed:#layout
    ]

! !

!UIObjectView methodsFor:'user actions - position'!

alignFrameLayout:aBlock
    "perform block on a frameLayout assigned to the current single selection
    "
    self transaction:#align selectionDo:[:aView|
        layout := self class asLayoutFrameFromView:aView.

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

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                bmost := (selection at:1) computeCorner y.

                self transaction:#align selectionDo:[:v|
                    (delta := bmost - (v computeCorner y)) ~~ 0 ifTrue:[
                        self shiftLayout:v top:delta bottom:delta.
                    ]
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout bottomOffset:0.
                    aLayout bottomFraction:1.0
                ]
            ]
        ].
        self changed:#layout
    ]



!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            view := self singleSelection.

            view notNil ifTrue:[
                view   := view superView.
                center := view computeExtent
            ] ifFalse:[
                view   := selection at:1.
                center := view computeCorner + view computeOrigin.
            ].
            center := center x // 2.

            self transaction:#align 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 changed:#layout
    ]



!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            view := self singleSelection.

            view notNil ifTrue:[
                view   := view superView.
                center := view computeExtent
            ] ifFalse:[
                view   := selection at:1.
                center := view computeCorner + view computeOrigin.
            ].
            center := center y // 2.

            self transaction:#align 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 changed:#layout
    ]
!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                lmost := (selection at:1) computeOrigin x.

                self transaction:#align selectionDo:[:v|
                    (delta := lmost - (v computeOrigin x)) ~~ 0 ifTrue:[
                        self shiftLayout:v left:delta right:delta
                    ]
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout leftOffset:0.
                    aLayout leftFraction:0.0.
                ]
            ]
        ].
        self changed:#layout
    ]
!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                lmost := (selection at:1) computeOrigin x.
                rmost := (selection at:1) computeCorner x.

                self transaction:#align selectionDo:[:v|
                    self shiftLayout:v left:(lmost - (v computeOrigin x))
                                     right:(rmost - (v computeCorner x)).

                    self elementChangedSize:v.
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout leftOffset:0.
                    aLayout leftFraction:0.0.
                    aLayout rightOffset:0.
                    aLayout rightFraction:1.0.
                ]
            ]
        ].
        self changed:#layout
    ].

!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                rmost := (selection at:1) computeCorner x.

                self transaction:#align selectionDo:[:v|
                    (delta := rmost - (v computeCorner x)) ~~ 0 ifTrue:[
                        self shiftLayout:v left:delta right:delta
                    ]
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout rightOffset:0.
                    aLayout rightFraction:1.0.
                ]
            ]
        ].
        self changed:#layout
    ]
!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                tmost := (selection at:1) computeOrigin y.

                self transaction:#align selectionDo:[:v|
                    (delta := tmost - (v computeOrigin y)) ~~ 0 ifTrue:[
                        self shiftLayout:v top:delta bottom:delta
                    ]
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout topOffset:0.
                    aLayout topFraction:0.0.
                ]
            ]
        ].
        self changed:#layout
    ]

!

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|

    (self canMove:selection) ifTrue:[
        self withSelectionHiddenDo:[
            self numberOfSelections > 1 ifTrue:[
                tmost := (selection at:1) computeOrigin y.
                bmost := (selection at:1) computeCorner y.

                self transaction:#align selectionDo:[:v|
                    self shiftLayout:v top:(tmost - (v computeOrigin y))
                                    bottom:(bmost - (v computeCorner y)).
                    self elementChangedSize:v.
                ]
            ] ifFalse:[
                self alignFrameLayout:[:aLayout|
                    aLayout topOffset:0.
                    aLayout topFraction:0.0.
                    aLayout bottomOffset:0.
                    aLayout bottomFraction:1.0.
                ]
            ]
        ].
        self changed:#layout
    ]
!

alignSingleSelection:aBlock

    |type layout|

    self withSelectionHiddenDo:[
        self transaction:#align selectionDo:[:aView|
            type := self class layoutType:aView.

            type notNil ifTrue:[
                self undoLayoutView:aView.

                layout := aView layout.

                type == #LayoutFrame ifFalse:[
                    layout := aView bounds asLayout
                ].
                aBlock value:layout.
                aView geometryLayout:layout.
            ]
        ]
    ].
    self changed:#layout



!

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 canMove:selection) ifFalse:[
        ^ self
    ].

    self withSelectionHiddenDo:[
        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.

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


!

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


!

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

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

    (self numberOfSelections > 1 and:[self canMove:selection]) 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:selection.
        topsInOrder  := viewsInOrder collect:[:aView | aView left].
        topsInOrder sortWith:viewsInOrder.

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

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

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

!

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

    (self numberOfSelections > 1 and:[self canMove:selection]) 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:selection.
        topsInOrder  := viewsInOrder collect:[:aView|aView top].
        topsInOrder sortWith:viewsInOrder.

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

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

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

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

openUndoMenu
    "open undo menu
    "
    self unselect.

    self withSelectionHiddenDo:[
        undoHistory openUndoMenu
    ].
    self changed:#tree

!

removeUndoHistory
    "delete total undo history
    "
    undoHistory reinitialize
!

undoLast
    "undo last action
    "
    self unselect.

    self withSelectionHiddenDo:[
        undoHistory undoLast:1
    ].
    self changed:#tree
! !

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

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


! !

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

new
    ^ self basicNew initialize


! !

!UIObjectView::UndoHistory methodsFor:'accessing'!

historySize
    ^ history size
! !

!UIObjectView::UndoHistory methodsFor:'initialization'!

initialize
    super initialize.
    self  reinitialize.


!

reinitialize
    "reinitialize all attributes
    "
    history     := OrderedCollection new.
    transaction := nil.
    enabled     := true.


! !

!UIObjectView::UndoHistory methodsFor:'menu'!

openUndoMenu
    |list 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.

    list := history collect:[:aTrans||e|
        e := MultiColListEntry new.
        e colAt:1 put:(aTrans type asString).
        e colAt:2 put:(aTrans text ? '').
        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


!

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

notEmpty
    "returns true if undo history is not empty
    "
    ^ history notEmpty


! !

!UIObjectView::UndoHistory methodsFor:'transaction'!

addUndoBlock:anUndoBlock
    "undo block to restore changes; add block to current transaction
    "
    self isTransactionOpen ifTrue:[
        transaction add:anUndoBlock
    ]


!

disabledTransitionDo:aBlock
    "disable transitions during evaluating the block
    "
    |oldState|

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

transaction:aType do:aBlock
    self transaction:aType text:nil do:aBlock
!

transaction: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:[
            history addLast:transaction.
            history size > (self class maxHistorySize) ifTrue:[history removeFirst]
        ].
        transaction := nil

    ] ifFalse:[
        aBlock value
    ]
! !

!UIObjectView::UndoHistory methodsFor:'undo'!

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

    transaction := nil.
    n := nTransactions min:(history size).

    n ~~ 0 ifTrue:[
        enabled := false.
        n timesRepeat:[ (history removeLast) undo ].
        enabled := true.
    ]


! !

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

version
    ^ '$Header$'
! !

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

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


! !

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

asString
    "returns printable string
    "
    |string|

    string := type asString.

    text notNil ifTrue:[^ string, '    ', text ]
               ifFalse:[^ string ]
!

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

type
    "returns type assigned to transition
    "
    ^ type
!

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

!UIObjectView::UndoHistory::Transaction methodsFor:'add & undo'!

add:anUndoBlock
    "add an undo action to the transition
    "
    actions isNil ifTrue:[
        actions := anUndoBlock
    ] ifFalse:[
        actions isCollection ifFalse:[
            |temp|

            temp := OrderedCollection new.
            temp add:actions.
            actions := temp.
        ].
        actions add:anUndoBlock.
    ]
!

undo
    "undo transition
    "
    actions notNil ifTrue:[
        actions isCollection ifFalse:[
            actions value
        ] ifTrue:[
            actions reverseDo:[:anUndoBlock| anUndoBlock value ]
        ]
    ]
! !

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

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

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

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

notEmpty
    "returns true if any undo action is registered
    "
    ^ actions notNil
! !

!UIObjectView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !