UIObjectView.st
author ca
Sat, 15 Feb 1997 19:14:01 +0100
changeset 49 7f58dd5fc836
parent 47 5e4319953a0b
child 50 fb4359c9bdc4
permissions -rw-r--r--
checkin from browser

ObjectView subclass:#UIObjectView
	instanceVariableNames:'inputView testMode undoHistory copiedExtent resizedObject
		resizeSelector createInWidget createFrame createdObject
		createClass clipChildren'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

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


!UIObjectView class methodsFor:'defaults'!

defaultGrid
    ^ 4 @ 4

!

gridShown
    ^ false

!

handleSize
    "size of blob drawn for handles"
    ^ 4

!

hitDelta
    ^ 4

! !

!UIObjectView methodsFor:'accessing'!

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

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

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

    ^ #(10 10 nil nil 10 10 false)


!

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


!

showGrid
    self withSelectionHiddenDo:[
        super showGrid
    ]

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


!

testMode
    "returns testMode
    "
    ^ testMode


!

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

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


! !

!UIObjectView methodsFor:'event handling'!

doKeyInput:key
    ^ self


!

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

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


!

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

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


!

exposeX:x y:y width:w height:h
    "handle an expose event from device; redraw selection
    "
    super exposeX:x y:y width:w height:h.

    selection notNil ifTrue:[
        self selectionDo:[:v | self showSelected:v]
    ]


!

keyPress:key x:x y:y

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

    (key == #Delete or:[key == #BackSpace]) ifTrue: [
        selection notNil ifTrue:[
            self deleteSelection
        ]
    ] ifFalse:[
        keyPressAction notNil ifTrue:[
            keyPressAction value:key
        ]
    ]


!

processEvent:anEvent
    "catch expose events for components, and redraw its handles after
     the redraw when this happens
    "
    |view|

    selection notNil ifTrue:[
        anEvent type == #damage ifTrue:[
            view := anEvent view.
            (selection == view
            or:[selection isCollection
                and:[selection includes:view]]) ifTrue:[
                    self showSelected:view
            ]
        ]
    ].
    ^ false.


!

sizeChanged:how
    self withSelectionHiddenDo:[
        super sizeChanged:how
    ]


! !

!UIObjectView methodsFor:'initialization'!

initialize
    super initialize.

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

    inputView eventReceiver:self.
    inputView enableButtonEvents.
    inputView enableButtonMotionEvents.

    self setDefaultActions.

    undoHistory := UndoHistory new.

    undoHistory modifiedAction:[:what|
        self changed:#undoHistory with:what
    ].

    testMode := false.
    clipChildren := true.

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

!

realize
    super realize.
    self windowGroup postEventHook:self

! !

!UIObjectView methodsFor:'misc'!

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


!

invertOutlineOf:anObject
    |wasClipped delta|

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

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

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

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


!

setDefaultActions

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

    self cursor:Cursor normal.

!

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

    |top|

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

! !

!UIObjectView methodsFor:'object creation'!

doDragCreate:aPoint
    "do a widget create drag
    "
    |p|

    p := self alignToGrid:aPoint.
    createFrame corner:(p - (createInWidget originRelativeTo:self)).

    (createFrame extent x < 10) ifTrue:[
        createFrame extent x:10
    ].

    (createFrame extent y < 10) ifTrue:[
        createFrame extent y:10
    ].

    self invertOutlineOf:createdObject.
    createdObject origin:(createFrame origin) extent:(createFrame extent).
    self invertOutlineOf:createdObject.
!

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

    self invertOutlineOf:createdObject.
    inputView raise.

    layout := createdObject bounds asLayout.
    createdObject geometryLayout:layout.

    self changed:#tree.
    self select:createdObject.
    createdObject := nil.

    self setDefaultActions.

!

setupCreatedObject:anObject
    self subclassResponsibility
!

startCreate:aPoint
    "start a widget create
    "
    |startPoint|

    createClass isNil ifTrue:[
        ^ self setDefaultActions
    ].
    (selection isKindOf:Collection) ifTrue:[
        self unselect.
      ^ self setDefaultActions.
    ].

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

    selection notNil ifTrue:[
        (    (self isPoint:aPoint containedIn:selection)
         and:[selection specClass basicNew supportsSubComponents]
        ) ifFalse:[
            self unselect
        ]
    ].

    oldCursor := cursor.
    self cursor:(Cursor leftHand).

    createInWidget := selection ? self.
    createdObject  := createClass new.
    createInWidget addSubView:createdObject.

    createFrame := Rectangle origin:(startPoint - (createInWidget originRelativeTo:self))
                             corner:startPoint.

    createdObject origin:(createFrame origin).

    undoHistory transactionNamed:'create' do:[
        self setupCreatedObject:createdObject.
    ].
    createdObject realize.
    self invertOutlineOf:createdObject.
! !

!UIObjectView methodsFor:'object moving'!

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

!

endObjectMove
    "cleanup after object move"

    movedObject notNil ifTrue:[
        movedObject do:[:aView|
            self invertOutlineOf:aView
        ].

        movedObject do:[:aView|
            self showSelected:aView
        ].
        movedObject size == 1 ifTrue:[
            selection := movedObject at:1
        ] ifFalse:[
            selection := movedObject
        ].

        movedObject := nil.
        self setDefaultActions.
        self changed:#layout.
    ].
!

startObjectMoveAt:aPoint

    self startObjectMove:selection at:aPoint.

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

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

    undoHistory transactionNamed:'move' do:[
        movedObject do:[:aView|
            self invertOutlineOf:aView.
            self undoBlockPositionChanged:aView
        ]
    ]
!

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

    |anObject|

    testMode ifTrue:[^ self].

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

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

    testMode ifTrue:[^ self].

    "if there is one selection and point hits handle, start a resize
    "
    self singleSelection notNil ifTrue:[
        b := self whichHandleOf:selection isHitBy:aPoint.

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

    anObject := self findObjectAt:aPoint.

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

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

    selection isCollection ifTrue:[
        releaseAction := [
            self setDefaultActions.
            self select:anObject
        ]
    ] ifFalse:[
        releaseAction := [self setDefaultActions]
    ].

    "prepare move operation for an object
    "
    motionAction := [:movePoint|
        (aPoint dist:movePoint) > 2.0 ifTrue:[
            self startObjectMoveAt:aPoint
        ]
    ].
! !

!UIObjectView methodsFor:'private handles'!

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

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

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

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

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

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


!

showSelected:aComponent
    |wasClipped delta oldPaint|

    self paint:Color black.

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

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

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

showUnselected:aComponent
    |wasClipped delta r oldPaint|

    r := aComponent origin extent:8@8.

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

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

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

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

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

    subViews do:[:anotherComponent |
        |absOrg absFrame|

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

!

whichHandleOf:aView isHitBy:aPoint
    |bounds|

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

    ^ #view

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

! !

!UIObjectView methodsFor:'private resizing-subviews'!

resize:aView bottom:aPoint

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

resize:aView corner:aPoint
    |delta|

    delta := aPoint - aView computeCorner.

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

resize:aView left:aPoint

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

!

resize:aView right:aPoint

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

resize:aView top:aPoint

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

!UIObjectView methodsFor:'private shift-layout'!

shifLayout:aView left:l right:r
    "shift layout for a view; in case of an open transaction, the
     undoAction will be defined
    "
    self shifLayout:aView top:0 bottom:0 left:l right:r

!

shifLayout:aView top:t bottom:b
    "shift layout for a view; in case of an open transaction, the
     undoAction will be defined
    "
    self shifLayout:aView top:t bottom:b left:0 right:0


!

shifLayout:aView top:t bottom:b left:l right:r
    "shift layout for a view; in case of an open transaction, the
     undoAction will be defined
    "
    |layout|

    self undoBlockPositionChanged:aView.

    layout := aView geometryLayout.

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

    layout isLayoutFrame ifTrue:[
        layout bottomOffset:(layout bottomOffset + b).
        layout  rightOffset:(layout rightOffset  + r).
    ].

    aView geometryLayout:layout.



! !

!UIObjectView methodsFor:'private undo-actions'!

undoBlockDimensionChanged:aView

    undoHistory isTransactionOpen ifTrue:[
        |layout|

        layout := aView geometryLayout copy.

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

!

undoBlockPositionChanged:aView

    undoHistory isTransactionOpen ifTrue:[
        |layout|

        layout := aView geometryLayout copy.
        undoHistory addUndoBlock:[aView geometryLayout:layout]
    ]

! !

!UIObjectView methodsFor:'searching'!

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

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

    inputView lower.

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

    inputView raise.

    view := device viewFromId:lastId.

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


!

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

    org := aView computeOrigin.
    ext := aView computeExtent.

    ^ ((org extent:ext) containsPoint:aPoint)
!

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

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

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

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

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

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

    ^ nil


! !

!UIObjectView methodsFor:'selections'!

addToSelection:something
    (testMode or:[something == selection]) ifFalse:[
        super addToSelection:something.
        self changed:#selection.
    ]
!

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

removeFromSelection:something
    super removeFromSelection:something.
    self changed:#selection

!

select:something
    (testMode or:[something == selection]) ifFalse:[
        super select:something.
        self changed:#selection
    ]

!

selection
    ^ selection


!

selectionFindMinimum:aOneArgBlock
    "returns the minimum value from the block evaluated on each view
     in the selection
    "
    |min val|

    self selectionDo:[:aView|
        val := aOneArgBlock value:aView.

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

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

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


!

singleSelection
    "returns single selection or nil
    "
    (selection isKindOf:SimpleView) ifTrue:[^ selection]
                                   ifFalse:[^ nil]
!

singleSelectionDo:aBlock

    self singleSelection notNil ifTrue:[
        aBlock value:selection
    ]
!

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

!

withSelectionHiddenDo:aBlock
    "evaluate aBlock while selection is hidden"

    |sel|

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

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


! !

!UIObjectView methodsFor:'testing'!

canMove:something
    ^ true


!

isHorizontalResizable:aComponent
    ^ self subclassResponsibility


!

isVerticalResizable:aComponent
    ^ self subclassResponsibility


! !

!UIObjectView methodsFor:'user actions'!

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


!

undoAction
    undoHistory notEmpty ifTrue:[
        self unselect.
        undoHistory undoLast
    ]


! !

!UIObjectView methodsFor:'user actions - dimension'!

copyExtent
    (selection isNil or:[selection isKindOf:Collection]) ifTrue:[
        ^ self warn:'exactly one element must be selected'.
    ].
    copiedExtent := selection computeExtent



!

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

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

!

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

!

setDimension:aLayout
    |undoText|

    undoText := 'change layout'.
    aLayout isLayout ifTrue:[
        undoText := 'change to layout frame'.
        aLayout isAlignmentOrigin ifTrue:[
            undoText := 'change to layout alignOrigin'.
        ] ifFalse:[
            aLayout isAlignmentOrigin ifTrue:[
                undoText := 'change to layout origin'.
            ]
        ]
    ].

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

!

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

!

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

!

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

!

transition:what dimensionDo:aOneArgBlock
    "change dimension within a transaction for the selected elements by evaluating
     the block with the argument a view.
    "
    self selectionHiddenDo:[
        undoHistory transactionNamed:what do:[
            self selectionDo:[:aView|
                self undoBlockDimensionChanged:aView.
                aOneArgBlock value:aView.
                self elementChangedLayout:aView.
            ]
        ]
    ]
! !

!UIObjectView methodsFor:'user actions - move'!

basicMoveSelectionHorizontal:n
    "move left:  n < 0
     move right: n > 0
    "
    self selectionHiddenDo:[
        undoHistory transactionNamed:'move' do:[
            self selectionDo:[:aView|self shifLayout:aView left:n right:n]
        ].
        self changed:#layout
    ]


!

basicMoveSelectionVertical:n
    "move up:   n < 0
     move down: n > 0
    "
    self selectionHiddenDo:[
        undoHistory transactionNamed:'move' do:[
            self selectionDo:[:aView| self shifLayout:aView top:n bottom:n ]
        ].
        self changed:#layout
    ]



!

moveObject:anObject to:aPoint
    "move anObject to newOrigin, aPoint
    "
    |dX dY org delta|

    anObject notNil ifTrue:[
        org := anObject computeOrigin.

        delta := aPoint - org.
        delta := (self alignToGrid:aPoint) - org.
        dX := delta x.
        dY := delta y.

        undoHistory disabledTransitionDo:[
            self shifLayout:anObject top:dY bottom:dY left:dX right:dX
        ].
        self elementChangedLayout:anObject.
    ]

!

moveSelectionDown
    self moveSelectionDown:1


!

moveSelectionDown10
    self moveSelectionDown:10


!

moveSelectionDown:n
    self basicMoveSelectionVertical:n


!

moveSelectionLeft
    self moveSelectionLeft:1


!

moveSelectionLeft10
    self moveSelectionLeft:10


!

moveSelectionLeft:n
    self basicMoveSelectionHorizontal:(n negated)


!

moveSelectionRight
    self moveSelectionRight:1


!

moveSelectionRight10
    self moveSelectionRight:10


!

moveSelectionRight:n
    self basicMoveSelectionHorizontal:n


!

moveSelectionUp
    self moveSelectionUp:1


!

moveSelectionUp10
    self moveSelectionUp:10


!

moveSelectionUp:n
    self basicMoveSelectionVertical:(n negated)


! !

!UIObjectView methodsFor:'user actions - position'!

alignSelectionBottom
    |bmost delta|

    self selectionHiddenDo:[
        bmost := 0.
        self selectionDo:[:v| bmost := bmost max:(v computeCorner y)].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v|
                (delta := bmost - (v computeCorner y)) ~~ 0 ifTrue:[
                    self shifLayout:v top:delta bottom:delta
                ]
            ]
        ].
        self changed:#layout
    ]



!

alignSelectionCenterHor
    |counter centerX|

    self selectionHiddenDo:[
        counter := 0.
        centerX := 0.

        self selectionDo:[:v |
            centerX := centerX + (v computeCorner x + v computeOrigin x).
            counter := counter + 1.
        ].
        centerX := centerX // (counter * 2).

        undoHistory transactionNamed:'align' do:[
            |newX oldX delta|

            self selectionDo:[:v|
                oldX  := v computeOrigin x.
                newX  := centerX - ((v computeCorner x - oldX) // 2).
                delta := newX - oldX.

                self shifLayout:v left:delta right:delta
            ]
        ].
        self changed:#layout
    ]



!

alignSelectionCenterVer
    |counter centerY|

    self selectionHiddenDo:[
        counter := 0.
        centerY := 0.

        self selectionDo:[:v |
            centerY := centerY + (v computeCorner y + v computeOrigin y).
            counter := counter + 1.
        ].
        centerY := centerY // (counter * 2).

        undoHistory transactionNamed:'align' do:[
            |newY oldY delta|

            self selectionDo:[:v|
                oldY  := v computeOrigin y.
                newY  := centerY - ((v computeCorner y - oldY) // 2).
                delta := newY - oldY.

                self shifLayout:v top:delta bottom:delta
            ]
        ].
        self changed:#layout
    ]
!

alignSelectionLeft
    |lmost delta|

    self selectionHiddenDo:[
        lmost := self selectionFindMinimum:[:v| v computeOrigin x].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v|
                (delta := lmost - (v computeOrigin x)) ~~ 0 ifTrue:[
                    self shifLayout:v left:delta right:delta
                ]
            ]
        ].
        self changed:#layout
    ]

!

alignSelectionLeftAndRight
    |lmost rmost|

    self selectionHiddenDo:[
        lmost := self selectionFindMinimum:[:v| v computeOrigin x].
        rmost := 0.
        self selectionDo:[:v | rmost := rmost max:(v computeCorner x)].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v|
                self shifLayout:v left:(lmost - (v computeOrigin x))
                                 right:(rmost - (v computeCorner x))
            ]
        ].
        self changed:#layout
    ]
!

alignSelectionRight
    |rmost delta|

    self selectionHiddenDo:[
        rmost := 0.
        self selectionDo:[:v| rmost := rmost max:(v computeCorner x)].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v|
                (delta := rmost - (v computeCorner x)) ~~ 0 ifTrue:[
                    self shifLayout:v left:delta right:delta
                ]
            ]
        ].
        self changed:#layout
    ]

!

alignSelectionTop
    |tmost delta|

    self selectionHiddenDo:[
        tmost := self selectionFindMinimum:[:v| v computeOrigin y].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v||delta|
                (delta := tmost - (v computeOrigin y)) ~~ 0 ifTrue:[
                    self shifLayout:v top:delta bottom:delta
                ]
            ]
        ].
        self changed:#layout
    ]

!

alignSelectionTopAndBottom
    |tmost bmost|

    self selectionHiddenDo:[
        tmost := self selectionFindMinimum:[:v| v computeOrigin y].
        bmost := 0.
        self selectionDo:[:v| bmost := bmost max:(v computeCorner y)].

        undoHistory transactionNamed:'align' do:[
            self selectionDo:[:v|
                self shifLayout:v top:(tmost - (v computeOrigin y))
                               bottom:(bmost - (v computeCorner y))
            ]
        ].
        self changed:#layout
    ]
!

centerSelection:aOneArgBlockXorY
    "center selection horizontal or vertical dependant on the block result( x or y).
     The argument to the block is the point.
    "
    |superview min max delta val|

    self selectionHiddenDo:[
        max := 0.

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

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

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

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

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

            undoHistory transactionNamed:'center' do:[
                self selectionDo:[:aView|
                    self shifLayout:aView top:delta bottom:delta]
            ]
        ].
        self changed:#layout
    ]


!

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


!

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

spreadSelectionHor
    |sumWidths min max viewsInOrder topsInOrder count space|

    (selection isKindOf:Collection) ifFalse:[^ self].

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

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

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

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

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

        undoHistory transactionNamed:'spread' do:[
            viewsInOrder do:[:aView | 
                |delta|

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

!

spreadSelectionVer
    |sumHeights min max viewsInOrder topsInOrder count space|

    (selection isKindOf:Collection) ifFalse:[^ self].

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

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

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

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

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

        undoHistory transactionNamed:'spread' do:[
            viewsInOrder do:[:aView||delta|
                delta := min - aView computeOrigin y.
                self shifLayout:aView top:delta bottom:delta.
                min := min + aView height + space
            ]
        ].
        self changed:#layout
    ]
! !

!UIObjectView methodsFor:'user actions - resize'!

doDragResize:aPoint
    "do a widget resize drag"

    |p|

    self invertOutlineOf:resizedObject.
    p := (self alignToGrid:aPoint) - (resizedObject container originRelativeTo:self).
    self perform:('x' , resizeSelector , ':') asSymbol with:p.
    resizedObject geometryLayout:(resizedObject geometryLayout).
    self invertOutlineOf:resizedObject

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

!

endResize
    "cleanup after object resize"

    self invertOutlineOf:resizedObject.
    self setDefaultActions.
    self select:resizedObject.
    resizedObject := nil

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

!

startResizeBorder:b of:selection at:aPoint
    "resize selected view
    "
    resizedObject := self singleSelection.

    resizedObject notNil ifTrue:[
        resizeSelector := b.
        super unselect.

        undoHistory transactionNamed:'extent' do:[
            self undoBlockDimensionChanged:resizedObject.
        ].

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

xbottom:aPoint
    self resize:resizedObject bottom:aPoint

!

xbottomLeft:aPoint
    self resize:resizedObject   left:aPoint.
    self resize:resizedObject bottom:aPoint.

!

xcorner:aPoint
    self resize:resizedObject corner:aPoint.

!

xleft:aPoint
    self resize:resizedObject left:aPoint

!

xorigin:aPoint
    self resize:resizedObject left:aPoint.
    self resize:resizedObject  top:aPoint.

!

xright:aPoint
    self resize:resizedObject right:aPoint

!

xtop:aPoint
    self resize:resizedObject top:aPoint

!

xtopRight:aPoint
    self resize:resizedObject right:aPoint.
    self resize:resizedObject   top:aPoint.

! !

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

modifiedAction:aBlockWithOneArg
    "the block is evaluated whenever the history changed; the argument to the
     block is the newest transaction identifier retrived from 'openTransaction'
    "
    modifiedAction := aBlockWithOneArg


! !

!UIObjectView::UndoHistory methodsFor:'initialization'!

initialize
    super initialize.
    self  reinitialize.


!

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


! !

!UIObjectView::UndoHistory methodsFor:'notifications'!

modified
    "raise notification; history changed
    "
    modifiedAction notNil ifTrue:[
        |what|

        history isEmpty ifTrue:[what := nil]
                       ifFalse:[what := history last first].

        modifiedAction value:what
    ]


! !

!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
    "
    enabled ifTrue:[
        transaction isNil ifTrue:[
            "no existing transaction
            "
            self halt
        ] ifFalse:[
            (transaction at:2) add:anUndoBlock
        ]
    ]


!

closeTransaction
    "close current transaction
    "
    self isTransactionOpen ifTrue:[
        transaction last isEmpty ifTrue:[
            "empty undo transaction
            "
            transaction := nil
        ] ifFalse:[
            history addLast:transaction.
            transaction := nil.

            history size > (self class maxHistorySize) ifTrue:[
                history removeFirst
            ].
            self modified
        ]
    ]


!

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

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

openTransaction:what
    "open a new transaction
    "
    enabled ifTrue:[
        transaction notNil ifTrue:[
            "transaction within transaction
            "
            self halt.
        ] ifFalse:[
            transaction := Array with:what with:OrderedCollection new
        ]
    ]

!

transactionNamed:what do:aBlock
    "open a transaction; perform the block; at least close the transaction
    "
    self isTransactionOpen ifFalse:[
        self openTransaction:what.
        aBlock value.
        self closeTransaction
    ] ifTrue:[
        aBlock value
    ]
! !

!UIObjectView::UndoHistory methodsFor:'undo'!

undoLast
    "undo last transactions; an open transaction will be closed;
     transactions during undo are disabled
    "
    self undoLast:1


!

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

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

    n ~~ 0 ifTrue:[
        enabled := false.

        n timesRepeat:[
            actions := (history removeLast) last.

            actions reverseDo:[:aUndoBlock|
                aUndoBlock value
            ]
        ].
        enabled := true.
        self modified.
    ]


! !

!UIObjectView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !