UIObjectView.st
author ca
Fri, 21 Feb 1997 20:33:57 +0100
changeset 58 668eb9eae2ac
parent 55 19e021c8f1ef
child 59 0a2b2ff030a0
permissions -rw-r--r--
*** empty log message ***

ObjectView subclass:#UIObjectView
	instanceVariableNames:'inputView testMode undoHistory copiedExtent actionData
		createClass clipChildren'
	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:'defaults'!

defaultGrid
    ^ 4 @ 4

!

gridShown
    ^ false

!

handleSize
    "size of blob drawn for handles"
    ^ 4

!

hitDelta
    ^ 4

! !

!UIObjectView methodsFor:'accessing'!

gridParameters
    "used by defineGrid, and in a separate method for
     easier redefinition in subclasses. 
     Returns the grid parameters in an array of 7 elements,
     which control the appearance of the grid-pattern.
     the elements are:

        bigStepH        number of pixels horizontally between 2 major steps
        bigStepV        number of pixels vertically between 2 major steps
        littleStepH     number of pixels horizontally between 2 minor steps
        littleStepV     number of pixels vertically between 2 minor steps
        gridAlignH      number of pixels for horizontal grid align (pointer snap)
        gridAlignV      number of pixels for vertical grid align (pointer snap)
        docBounds       true, if document boundary should be shown

     if littleStepH/V are nil, only bigSteps are drawn.
    "

    ^ #(10 10 nil nil 10 10 false)


!

hideGrid
    gridShown ifTrue:[
        self withSelectionHiddenDo:[
            super hideGrid
        ]
    ]


!

showGrid
    self withSelectionHiddenDo:[
        super showGrid
    ]

    "Modified: 5.9.1995 / 12:47:46 / claus"


!

testMode
    "returns testMode
    "
    ^ testMode


!

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

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


! !

!UIObjectView methodsFor:'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'!

elementChanged:aView 
    "some element has been changed - kludge to force a resizing
     operation (for child layout recomputation) in its superView"

    aView superView sizeChanged:nil.
    self changed:#any.


!

elementChangedLayout:aView 
    "some element has been changed - kludge to force a resizing
     operation (for child layout recomputation) in its superView"

    aView superView sizeChanged:nil.
    self changed:#layout.


!

exposeX:x y:y width:w height:h
    "handle an expose event from device; redraw selection
    "
    super exposeX:x y:y width:w height:h.
    self selectionDo:[:v | self showSelected:v]


!

keyPress:key x:x y:y
    <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
    self withSelectionHiddenDo:[
        super sizeChanged:how
    ]


! !

!UIObjectView methodsFor:'initialization'!

initialize
    super initialize.

    "funny: since I do not want the created widgets to get pointer
     events, I put an InputView on top of them, which catches those events
     and passes them back to me - have to take care, that this inputView
     is always on top
    "
    inputView := InputView origin:0.0@0.0 extent:1.0@1.0 in:self.

    inputView eventReceiver:self.
    inputView enableButtonEvents.
    inputView enableButtonMotionEvents.

    self setDefaultActions.

    undoHistory  := UndoHistory new.
    testMode     := false.
    clipChildren := true.

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

!

realize
    super realize.
    self windowGroup postEventHook:self

! !

!UIObjectView methodsFor:'misc'!

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


!

invertOutlineOf:anObject
    |wasClipped delta|

    (wasClipped := clipChildren) ifTrue:[
        self clippedByChildren:(clipChildren := false).
    ].
    delta := (anObject originRelativeTo:self) - anObject origin.

    self xoring:[
        self displayRectangle:((anObject origin + delta) extent:anObject extent).
    ].

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

    "Modified: 5.9.1995 / 12:25:25 / claus"


!

setDefaultActions

    pressAction      := [:pressPoint | self startSelectOrMove:pressPoint].
    shiftPressAction := [:pressPoint | self startSelectMoreOrMove:pressPoint].
    motionAction     := [:movePoint  | nil].
    releaseAction    := [nil].
    keyPressAction   := nil.

    self cursor:Cursor normal.

!

showDragging:something offset:anOffset
    "drag around a View"

    |top|

    self forEach:something do:[:anObject |
        self drawRectangle:((anObject origin + anOffset) extent:(anObject extent))
    ]

! !

!UIObjectView methodsFor:'object creation'!

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|

    self invertOutlineOf:(actionData object).
    inputView raise.

    layout := (actionData object) bounds asLayout.
    (actionData object) geometryLayout:layout.

    self changed:#tree.
    self select:(actionData 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.
    ].

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

    widget := self singleSelection.

    (     widget notNil
     and:[(self isPoint:aPoint containedIn:widget)
     and:[self supportsSubComponents:widget]]
    ) ifFalse:[
        self unselect.
        widget := self.
    ].

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

    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 undoBlockPositionChanged:aView
    ].

!

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

    |anObject|

    testMode ifTrue:[^ self].

    anObject := self findObjectAt:aPoint.
    anObject notNil ifTrue:[
        (self isSelected:anObject) ifTrue:[
            self removeFromSelection:anObject
        ] ifFalse:[
            self addToSelection:anObject
        ]
    ]
!

startSelectOrMove:aPoint
    "a button is pressed at a point
    "
    |anObject b|

    testMode ifTrue:[^ self].

    "if there is one object selected and point hits a handle, start a resize
    "
    anObject := self singleSelection.

    anObject notNil ifTrue:[
        b := self whichHandleOf:anObject isHitBy:aPoint.

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

    anObject := self findObjectAt:aPoint.

    "nothing is selected
    "
    anObject isNil ifTrue:[
        ^ self unselect
    ].

    (self isSelected:anObject) ifFalse:[
        super unselect.
        self select:anObject.
    ].

    (self numberOfSelections ~~ 1) ifTrue:[
        releaseAction := [
            self setDefaultActions.
            self select:anObject
        ]
    ] 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"

    self invertOutlineOf:(actionData object).
    self setDefaultActions.
    self select:(actionData object).
    actionData := nil

    "Modified: 5.9.1995 / 17:11:17 / claus"

!

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

    object := self singleSelection.

    (object geometryLayout) isNil ifTrue:[
        ^ self setDefaultActions.
    ].

    self actionResize:object selector:b.

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

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

!UIObjectView methodsFor:'private handles'!

handlesOf:aComponent do:aBlock
    |delta layout vertical horizontal|

    layout := aComponent geometryLayout.
    delta  := (aComponent originRelativeTo:self) - aComponent origin.

    (layout isLayout not or:[layout isLayoutFrame]) ifTrue:[
        vertical   := self isVerticalResizable:aComponent.
        horizontal := self isHorizontalResizable:aComponent.
    ] ifFalse:[
        vertical   := false.
        horizontal := false.
    ].

    horizontal ifTrue:[
        aBlock value:(aComponent leftCenter   + delta) value:#left.
        aBlock value:(aComponent rightCenter  + delta) value:#right.
    ].

    vertical ifTrue:[
        aBlock value:(aComponent topCenter    + delta) value:#top.
        aBlock value:(aComponent bottomCenter + delta) value:#bottom.
    ].

    (horizontal and:[vertical]) ifTrue:[
        aBlock value:(aComponent origin     + delta) value:#origin.
        aBlock value:(aComponent corner     + delta) value:#corner.
        aBlock value:(aComponent topRight   + delta) value:#topRight.
        aBlock value:(aComponent bottomLeft + delta) value:#bottomLeft.
    ] ifFalse:[
        aBlock value:(aComponent origin     + delta) value:#view.
        aBlock value:(aComponent corner     + delta) value:#view.
        aBlock value:(aComponent topRight   + delta) value:#view.
        aBlock value:(aComponent bottomLeft + delta) value:#view.
    ].

!

showSelected:aComponent
    |wasClipped delta oldPaint|

    self paint:Color black.

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

    self handlesOf:aComponent do:[:pnt :what |
        what == #view ifTrue:[self displayRectangle:(pnt - (4@4) extent:7@7)]
                     ifFalse:[self    fillRectangle:(pnt - (4@4) extent:7@7)]
    ].

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

showUnselected:aComponent
    |wasClipped delta r oldPaint|

    r := aComponent origin extent:8@8.

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

    self handlesOf:aComponent do:[:pnt :what |
        self clearRectangle:(pnt - (4@4) extent:7@7).
    ].

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

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

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

    subViews do:[:anotherComponent |
        |absOrg absFrame|

        anotherComponent ~~ inputView ifTrue:[
            absOrg := anotherComponent originRelativeTo:self.
            absFrame := absOrg extent:(anotherComponent extent).
            (absFrame intersects:r) ifTrue:[
                anotherComponent withAllSubViewsDo:[:v |
                    v clear.
                    v exposeX:0 y:0 width:9999 height:9999.
                ]
            ]
        ]
    ]

!

whichHandleOf:aView isHitBy:aPoint
    |bounds|

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

    ^ nil

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

! !

!UIObjectView methodsFor:'private resizing-subviews'!

resize:aView bottom:aPoint

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

resize:aView bottomLeft:aPoint

    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
    |delta|

    delta := aPoint - aView computeCorner.

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

resize:aView left:aPoint

    undoHistory disabledTransitionDo:[
        self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
    ]

!

resize:aView origin:aPoint
    |delta|

    delta := aPoint - aView computeOrigin.

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

!

resize:aView right:aPoint

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

resize:aView top:aPoint

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

resize:aView topRight:aPoint

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

    layout := aView geometryLayout.

    layout isLayout ifTrue:[
        self undoBlockPositionChanged:aView.

        layout leftOffset:(layout leftOffset + l)
                topOffset:(layout topOffset  + t).

        layout isLayoutFrame ifTrue:[
            layout bottomOffset:(layout bottomOffset + b).
            layout  rightOffset:(layout rightOffset  + r).
        ].
        aView geometryLayout:layout.
    ] ifFalse:[
        |pixelOrigin|

        self undoBlockPositionChanged:aView.

        pixelOrigin := aView pixelOrigin.
        pixelOrigin := pixelOrigin + (l@t).
        aView pixelOrigin:pixelOrigin
    ]


! !

!UIObjectView methodsFor:'searching'!

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

    viewId := rootView id.
    point  := aPoint + (device translatePoint:0@0 from:(self id) to:viewId).

    inputView lower.

    [viewId notNil] whileTrue:[
        lastId := viewId.
        viewId := device viewIdFromPoint:point in:lastId
    ].

    inputView raise.

    view := device viewFromId:lastId.

    view ~~ inputView ifTrue:[^ view]
                     ifFalse:[^ nil]


!

isPoint:aPoint containedIn:aView
    "checks whether a point is covered by a view.
    "
    |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
    (self canSelect:something) ifTrue:[
        super addToSelection:something.
        self changed:#selection.
    ]
!

inspectSelection
    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
    super removeFromSelection:something.
    self changed:#selection

!

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

!

selection
    ^ selection


!

selectionHiddenDo:aBlock
    "apply block to every object in selection"

    self selectionDo:[:aView |
        self showUnselected:aView.
    ].
    device flush.
    aBlock value.
    self selectionDo:[:aView |
        self showSelected:aView
    ]


!

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

singleSelectionDo:aBlock
    |view|

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

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

!

withSelectionHiddenDo:aBlock
    "evaluate aBlock while selection is hidden"

    |sel|

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

    "Modified: 6.9.1995 / 01:46:16 / claus"


! !

!UIObjectView methodsFor:'testing'!

canMove:something
    ^ true


!

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

!

canSelect:something
    ^ (testMode not and:[something ~~ selection])

!

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

isHorizontalResizable:aComponent
    ^ self subclassResponsibility


!

isVerticalResizable:aComponent
    ^ self subclassResponsibility


!

supportsSubComponents:something
    "returns true if somrthing supports subcomponents
    "
    |specClass|

    something notNil ifTrue:[
        something isCollection ifFalse:[
            specClass := something specClass
        ] ifTrue:[
            something size == 1 ifTrue:[
                specClass := (something at:1) specClass
            ]
        ].
        specClass notNil ifTrue:[
            ^ specClass basicNew supportsSubComponents
        ]
    ].
    ^ false
! !

!UIObjectView methodsFor:'transaction & undo'!

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


!

undoBlockDimensionChanged:aView

    undoHistory isTransactionOpen ifTrue:[
        |layout|

        layout := aView geometryLayout copy.

        undoHistory addUndoBlock:[
            aView geometryLayout:layout.
            aView superView sizeChanged:nil.
        ]
    ]

!

undoBlockPositionChanged:aView

    undoHistory isTransactionOpen ifTrue:[
        |layout|

        layout := aView geometryLayout copy.
        layout isNil ifFalse:[
            undoHistory addUndoBlock:[aView geometryLayout:layout]
        ] ifTrue:[
            layout := aView pixelOrigin.
            undoHistory addUndoBlock:[aView pixelOrigin:layout]
        ]
    ]

!

undoDeleteAll
    "delete total undo history
    "
    undoHistory reinitialize
!

undoLast
    self undoLast:1
!

undoLast:n

    self unselect.
    undoHistory undoLast:n.
    self changed:#tree


! !

!UIObjectView methodsFor:'user actions - dimension'!

copyExtent
    |object|

    object := self singleSelection.

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



!

pasteExtent
    copiedExtent notNil ifTrue:[
        self transition:#extent dimensionDo:[:v|
            self resize:v corner:(v computeOrigin + copiedExtent)
        ]    
    ]    
!

pasteHeight
    copiedExtent notNil ifTrue:[
        self transition:'paste height' dimensionDo:[:v|
            self resize:v bottom:(v computeOrigin + copiedExtent)
        ]    
    ]    

!

pasteWidth
    copiedExtent notNil ifTrue:[
        self transition:'paste width' dimensionDo:[:v|
            self resize:v right:(v computeOrigin + copiedExtent)
        ]    
    ]    

!

setDimension:aLayout
    |type|

    aLayout isLayout ifTrue:[
        aLayout isLayoutFrame ifTrue:[
            type := #layoutFrame
        ] ifFalse:[
            aLayout isAlignmentOrigin ifTrue:[
                type := #layoutAlignOrigin.
            ] ifFalse:[
                type := #layoutOrigin
            ]
        ]
    ] ifFalse:[
        type := #layout
    ].

    self transition:type dimensionDo:[:v| v geometryLayout:(aLayout copy)]    

!

setToDefaultExtent
    self transition:#extent dimensionDo:[:v|
        self resize:v corner:(v computeOrigin + (v preferredExtent))
    ]    

!

setToDefaultHeight
    self transition:'default height' dimensionDo:[:v|
        self resize:v bottom:(v computeOrigin + (v preferredExtent))
    ]    

!

setToDefaultWidth
    self transition:'default width' dimensionDo:[:v|
        self resize:v right:(v computeOrigin + (v preferredExtent))
    ]    

!

transition:aType dimensionDo:aOneArgBlock
    "change dimension within a transaction for the selected elements by evaluating
     the block with the argument a view.
    "
    self selectionHiddenDo:[
        self transaction:aType selectionDo:[:aView|
            self undoBlockDimensionChanged:aView.
            aOneArgBlock value:aView.
            aView superView sizeChanged:nil
        ].
        self changed:#layout
    ]
! !

!UIObjectView methodsFor:'user actions - move'!

moveSelectionDown:aNumber
    |gridY|

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

    self selectionHiddenDo:[
        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|

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

    self selectionHiddenDo:[
        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|

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

    self selectionHiddenDo:[
        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|

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

    self selectionHiddenDo:[
        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'!

alignSelectionBottom
    |bmost delta layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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:[
                layout := selection geometryLayout.

                (layout isLayout and:[layout isLayoutFrame]) ifFalse:[
                    ^ self
                ].

                self transaction:#layout selectionDo:[:aView|
                    self undoBlockDimensionChanged:aView.
                    layout := aView geometryLayout.
                    layout bottomOffset:0.
                    layout bottomFraction:1.0.
                    aView geometryLayout:layout.
                ]
            ]
        ].
        self changed:#layout
    ]



!

alignSelectionCenterHor
    |view center|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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
    |view center|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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
    |lmost delta layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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 transaction:#layout selectionDo:[:aView|
                    layout := aView geometryLayout.

                    layout isLayout ifTrue:[
                        self undoBlockDimensionChanged:aView.
                        layout leftOffset:0.
                        layout leftFraction:0.0.
                        aView geometryLayout:layout.
                    ]
                ]
            ]
        ].
        self changed:#layout
    ]
!

alignSelectionLeftAndRight
    |lmost rmost layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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))
                ]
            ] ifFalse:[
                self transaction:#layout selectionDo:[:aView|
                    layout := aView geometryLayout.

                    layout isLayout ifTrue:[
                        self undoBlockDimensionChanged:aView.
                        layout leftOffset:0.
                        layout leftFraction:0.0.

                        (layout isLayout and:[layout isLayoutFrame]) ifTrue:[
                            layout rightOffset:0.
                            layout rightFraction:1.0.
                        ].
                        aView geometryLayout:layout.
                    ]
                ]
            ]
        ].
        self changed:#layout
    ]
!

alignSelectionRight
    |rmost delta layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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:[
                layout := selection geometryLayout.

                (layout isLayout and:[layout isLayoutFrame]) ifFalse:[
                    ^ self
                ].

                self transaction:#layout selectionDo:[:aView|
                    self undoBlockDimensionChanged:aView.
                    layout := aView geometryLayout.
                    layout rightOffset:0.
                    layout rightFraction:1.0.
                    aView geometryLayout:layout.
                ]
            ]
        ].
        self changed:#layout
    ]
!

alignSelectionTop
    |tmost delta layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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 transaction:#layout selectionDo:[:aView|
                    layout := aView geometryLayout.

                    layout isLayout ifTrue:[
                        self undoBlockDimensionChanged:aView.
                        layout topOffset:0.
                        layout topFraction:0.0.
                        aView geometryLayout:layout.
                    ]
                ]
            ]
        ].
        self changed:#layout
    ]

!

alignSelectionTopAndBottom
    |tmost bmost layout|

    selection notNil ifTrue:[
        self selectionHiddenDo:[
            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))
                ]
            ] ifFalse:[
                self transaction:#layout selectionDo:[:aView|
                    layout := aView geometryLayout.

                    layout isLayout ifTrue:[
                        self undoBlockDimensionChanged:aView.
                        layout topOffset:0.
                        layout topFraction:0.0.

                        (layout isLayout and:[layout isLayoutFrame]) ifTrue:[
                            layout bottomOffset:0.
                            layout bottomFraction:1.0.
                        ].
                        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 selectionHiddenDo:[
        max := 0.

        self selectionDo:[:aView |
            superview isNil ifTrue:[
                superview := aView superView
            ] ifFalse:[
                (aView superView == superview) ifFalse:[
                    ^ self notify:'views must have same superview'.
                ]
            ].
            val := aOneArgBlockXorY value:(aView computeOrigin).    

            min isNil ifTrue:[min := val]
                     ifFalse:[min := min min:val].

            val := aOneArgBlockXorY value:(aView computeCorner).
            max := max max:val.
        ].

        val := aOneArgBlockXorY value:(superview computeExtent).
        max := (min + val - max) // 2.

        max == min ifFalse:[
            delta := max - min.

            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
    |sumWidths min max viewsInOrder topsInOrder count space|

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

    self selectionHiddenDo:[
        count := 0.
        sumWidths := 0.
        max := 0.

        self selectionDo:[:aView |
            sumWidths := sumWidths + aView width.

            min isNil ifTrue:[min := aView left]
                     ifFalse:[min := min min:(aView left)].

            max := max max:(aView right).
            count := count + 1
        ].
        viewsInOrder := Array withAll:selection.
        topsInOrder  := viewsInOrder collect:[:aView | aView left].
        topsInOrder sortWith:viewsInOrder.

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

        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
    |sumHeights min max viewsInOrder topsInOrder count space|

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

    self selectionHiddenDo:[
        count := 0.
        sumHeights := 0.
        max := 0.

        self selectionDo:[:aView |
            sumHeights := sumHeights + aView height.

            min isNil ifTrue:[min := aView top]
                     ifFalse:[min := min min:(aView top)].

            max   := max max:(aView bottom).
            count := count + 1
        ].
        viewsInOrder := Array withAll:selection.
        topsInOrder  := viewsInOrder collect:[:aView|aView top].
        topsInOrder sortWith:viewsInOrder.

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

        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::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'!

popupMenu
    "returns a submenu for undo
    "
    |labels|

    labels := OrderedCollection new:(history size).
    history reverseDo:[:aRecord| labels add:(aRecord asString) ].

    ^ PopUpMenu labels:labels selectors:#undoLast:.

! !

!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:'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$'
! !