UIObjectView.st
changeset 59 0a2b2ff030a0
parent 58 668eb9eae2ac
child 60 7542ab7fbbfe
equal deleted inserted replaced
58:668eb9eae2ac 59:0a2b2ff030a0
     1 ObjectView subclass:#UIObjectView
       
     2 	instanceVariableNames:'inputView testMode undoHistory copiedExtent actionData
       
     3 		createClass clipChildren'
       
     4 	classVariableNames:''
       
     5 	poolDictionaries:''
       
     6 	category:'Interface-UIPainter'
       
     7 !
       
     8 
       
     9 Object subclass:#UndoHistory
       
    10 	instanceVariableNames:'history transaction enabled'
       
    11 	classVariableNames:''
       
    12 	poolDictionaries:''
       
    13 	privateIn:UIObjectView
       
    14 !
       
    15 
       
    16 Object subclass:#Transaction
     1 Object subclass:#Transaction
    17 	instanceVariableNames:'type text actions'
     2 	instanceVariableNames:'type text actions'
    18 	classVariableNames:''
     3 	classVariableNames:''
    19 	poolDictionaries:''
     4 	poolDictionaries:''
    20 	privateIn:UIObjectView::UndoHistory
     5 	privateIn:UIObjectView::UndoHistory
    21 !
     6 !
    22 
       
    23 
       
    24 !UIObjectView class methodsFor:'defaults'!
       
    25 
       
    26 defaultGrid
       
    27     ^ 4 @ 4
       
    28 
       
    29 !
       
    30 
       
    31 gridShown
       
    32     ^ false
       
    33 
       
    34 !
       
    35 
       
    36 handleSize
       
    37     "size of blob drawn for handles"
       
    38     ^ 4
       
    39 
       
    40 !
       
    41 
       
    42 hitDelta
       
    43     ^ 4
       
    44 
       
    45 ! !
       
    46 
       
    47 !UIObjectView methodsFor:'accessing'!
       
    48 
       
    49 gridParameters
       
    50     "used by defineGrid, and in a separate method for
       
    51      easier redefinition in subclasses. 
       
    52      Returns the grid parameters in an array of 7 elements,
       
    53      which control the appearance of the grid-pattern.
       
    54      the elements are:
       
    55 
       
    56         bigStepH        number of pixels horizontally between 2 major steps
       
    57         bigStepV        number of pixels vertically between 2 major steps
       
    58         littleStepH     number of pixels horizontally between 2 minor steps
       
    59         littleStepV     number of pixels vertically between 2 minor steps
       
    60         gridAlignH      number of pixels for horizontal grid align (pointer snap)
       
    61         gridAlignV      number of pixels for vertical grid align (pointer snap)
       
    62         docBounds       true, if document boundary should be shown
       
    63 
       
    64      if littleStepH/V are nil, only bigSteps are drawn.
       
    65     "
       
    66 
       
    67     ^ #(10 10 nil nil 10 10 false)
       
    68 
       
    69 
       
    70 !
       
    71 
       
    72 hideGrid
       
    73     gridShown ifTrue:[
       
    74         self withSelectionHiddenDo:[
       
    75             super hideGrid
       
    76         ]
       
    77     ]
       
    78 
       
    79 
       
    80 !
       
    81 
       
    82 showGrid
       
    83     self withSelectionHiddenDo:[
       
    84         super showGrid
       
    85     ]
       
    86 
       
    87     "Modified: 5.9.1995 / 12:47:46 / claus"
       
    88 
       
    89 
       
    90 !
       
    91 
       
    92 testMode
       
    93     "returns testMode
       
    94     "
       
    95     ^ testMode
       
    96 
       
    97 
       
    98 !
       
    99 
       
   100 testMode:aBoolean
       
   101     "change testMode
       
   102     "
       
   103     (aBoolean == testMode) ifFalse:[
       
   104         testMode := aBoolean.
       
   105 
       
   106         testMode ifTrue:[
       
   107             self unselect.
       
   108             inputView unrealize
       
   109         ] ifFalse:[
       
   110             inputView raise.
       
   111             inputView realize
       
   112         ]
       
   113     ]
       
   114 
       
   115 
       
   116 ! !
       
   117 
       
   118 !UIObjectView methodsFor:'blocked'!
       
   119 
       
   120 addObject:anObject
       
   121     "add the argument, anObject to the contents - with redraw"
       
   122 
       
   123     self halt
       
   124 
       
   125 !
       
   126 
       
   127 addObjectWithoutRedraw:anObject
       
   128     "add the argument, anObject to the contents - with redraw"
       
   129 
       
   130     self halt
       
   131 
       
   132 ! !
       
   133 
       
   134 !UIObjectView methodsFor:'event handling'!
       
   135 
       
   136 elementChanged:aView 
       
   137     "some element has been changed - kludge to force a resizing
       
   138      operation (for child layout recomputation) in its superView"
       
   139 
       
   140     aView superView sizeChanged:nil.
       
   141     self changed:#any.
       
   142 
       
   143 
       
   144 !
       
   145 
       
   146 elementChangedLayout:aView 
       
   147     "some element has been changed - kludge to force a resizing
       
   148      operation (for child layout recomputation) in its superView"
       
   149 
       
   150     aView superView sizeChanged:nil.
       
   151     self changed:#layout.
       
   152 
       
   153 
       
   154 !
       
   155 
       
   156 exposeX:x y:y width:w height:h
       
   157     "handle an expose event from device; redraw selection
       
   158     "
       
   159     super exposeX:x y:y width:w height:h.
       
   160     self selectionDo:[:v | self showSelected:v]
       
   161 
       
   162 
       
   163 !
       
   164 
       
   165 keyPress:key x:x y:y
       
   166     <resource: #keyboard ( #InspectIt #Delete #BackSpace #Cut) >
       
   167 
       
   168     key == #InspectIt ifTrue:[
       
   169         ^ self inspectSelection
       
   170     ].
       
   171 
       
   172     (key == #Cut or:[key == #Delete or:[key == #BackSpace]]) ifTrue: [
       
   173         ^ self deleteSelection
       
   174     ].
       
   175 
       
   176     super keyPress:key x:x y:y
       
   177 
       
   178 
       
   179 !
       
   180 
       
   181 processEvent:anEvent
       
   182     "catch expose events for components, and redraw its handles after
       
   183      the redraw when this happens
       
   184     "
       
   185     |view|
       
   186 
       
   187     selection notNil ifTrue:[
       
   188         anEvent type == #damage ifTrue:[
       
   189             view := anEvent view.
       
   190             (selection == view
       
   191             or:[selection isCollection
       
   192                 and:[selection includes:view]]) ifTrue:[
       
   193                     self showSelected:view
       
   194             ]
       
   195         ]
       
   196     ].
       
   197     ^ false.
       
   198 
       
   199 
       
   200 !
       
   201 
       
   202 sizeChanged:how
       
   203     self withSelectionHiddenDo:[
       
   204         super sizeChanged:how
       
   205     ]
       
   206 
       
   207 
       
   208 ! !
       
   209 
       
   210 !UIObjectView methodsFor:'initialization'!
       
   211 
       
   212 initialize
       
   213     super initialize.
       
   214 
       
   215     "funny: since I do not want the created widgets to get pointer
       
   216      events, I put an InputView on top of them, which catches those events
       
   217      and passes them back to me - have to take care, that this inputView
       
   218      is always on top
       
   219     "
       
   220     inputView := InputView origin:0.0@0.0 extent:1.0@1.0 in:self.
       
   221 
       
   222     inputView eventReceiver:self.
       
   223     inputView enableButtonEvents.
       
   224     inputView enableButtonMotionEvents.
       
   225 
       
   226     self setDefaultActions.
       
   227 
       
   228     undoHistory  := UndoHistory new.
       
   229     testMode     := false.
       
   230     clipChildren := true.
       
   231 
       
   232     (self class gridShown) ifTrue:[
       
   233         super showGrid
       
   234     ].
       
   235 
       
   236 !
       
   237 
       
   238 realize
       
   239     super realize.
       
   240     self windowGroup postEventHook:self
       
   241 
       
   242 ! !
       
   243 
       
   244 !UIObjectView methodsFor:'misc'!
       
   245 
       
   246 cursor:aCursor
       
   247     inputView realized ifTrue:[
       
   248         inputView cursor:aCursor
       
   249     ].
       
   250     super cursor:aCursor
       
   251 
       
   252 
       
   253 !
       
   254 
       
   255 invertOutlineOf:anObject
       
   256     |wasClipped delta|
       
   257 
       
   258     (wasClipped := clipChildren) ifTrue:[
       
   259         self clippedByChildren:(clipChildren := false).
       
   260     ].
       
   261     delta := (anObject originRelativeTo:self) - anObject origin.
       
   262 
       
   263     self xoring:[
       
   264         self displayRectangle:((anObject origin + delta) extent:anObject extent).
       
   265     ].
       
   266 
       
   267     wasClipped ifTrue:[
       
   268         self clippedByChildren:(clipChildren := true).
       
   269     ].
       
   270 
       
   271     "Modified: 5.9.1995 / 12:25:25 / claus"
       
   272 
       
   273 
       
   274 !
       
   275 
       
   276 setDefaultActions
       
   277 
       
   278     pressAction      := [:pressPoint | self startSelectOrMove:pressPoint].
       
   279     shiftPressAction := [:pressPoint | self startSelectMoreOrMove:pressPoint].
       
   280     motionAction     := [:movePoint  | nil].
       
   281     releaseAction    := [nil].
       
   282     keyPressAction   := nil.
       
   283 
       
   284     self cursor:Cursor normal.
       
   285 
       
   286 !
       
   287 
       
   288 showDragging:something offset:anOffset
       
   289     "drag around a View"
       
   290 
       
   291     |top|
       
   292 
       
   293     self forEach:something do:[:anObject |
       
   294         self drawRectangle:((anObject origin + anOffset) extent:(anObject extent))
       
   295     ]
       
   296 
       
   297 ! !
       
   298 
       
   299 !UIObjectView methodsFor:'object creation'!
       
   300 
       
   301 actionCreate:anObject frame:aFrame delta:aDelta
       
   302     "create and initialize action data
       
   303     "
       
   304     |extent x y selectors values|
       
   305 
       
   306 "minimum extent
       
   307 "
       
   308     extent := self extent.
       
   309     x := extent x // 3.
       
   310     y := extent y // 3.
       
   311     extent := anObject preferredExtent.
       
   312 
       
   313     (extent x > x) ifTrue:[extent x:x].
       
   314     (extent y > y) ifTrue:[extent y:y].
       
   315 
       
   316 "setup structure
       
   317 "
       
   318     selectors := #( object frame delta vertical horizontal minExtent ).
       
   319     values    := Array new:(selectors size).
       
   320 
       
   321     values at:1 put:anObject.
       
   322     values at:2 put:aFrame.
       
   323     values at:3 put:aDelta.
       
   324     values at:4 put:(self isVerticalResizable:anObject).
       
   325     values at:5 put:(self isHorizontalResizable:anObject).
       
   326     values at:6 put:extent.
       
   327 
       
   328     actionData := Structure newWith:selectors values:values.
       
   329 
       
   330 
       
   331 "can change cursor dependent on vertical/horizontal resizing
       
   332 "
       
   333     oldCursor := cursor.
       
   334     self cursor:(Cursor leftHand).
       
   335 
       
   336 
       
   337 
       
   338 !
       
   339 
       
   340 createWidgetWithClass:aClass
       
   341     "prepare to create new widgets
       
   342     "
       
   343     createClass := aClass.
       
   344     pressAction := [:pressPoint | self startCreate:pressPoint].
       
   345     self cursor:Cursor origin.
       
   346 
       
   347 
       
   348 !
       
   349 
       
   350 doDragCreate:aPoint
       
   351     "do a widget create drag
       
   352     "
       
   353     |frame object extent minimum|
       
   354 
       
   355     frame   := actionData frame.
       
   356     frame corner:((self alignToGrid:aPoint) - (actionData delta)).
       
   357 
       
   358     object  := actionData object.
       
   359     minimum := actionData minExtent.
       
   360     extent  := frame extent.
       
   361 
       
   362     ((extent x < minimum x) or:[actionData horizontal not]) ifTrue:[
       
   363         extent x:(minimum x)
       
   364     ].
       
   365 
       
   366     ((extent y < minimum y) or:[actionData vertical not]) ifTrue:[
       
   367         extent y:(minimum y)
       
   368     ].
       
   369 
       
   370     frame extent:extent.
       
   371 
       
   372     self invertOutlineOf:object.
       
   373     object origin:(frame origin) extent:(frame extent).
       
   374     self invertOutlineOf:object.
       
   375 !
       
   376 
       
   377 endCreate
       
   378     "end a widget create drag
       
   379     "
       
   380     |layout x y|
       
   381 
       
   382     self invertOutlineOf:(actionData object).
       
   383     inputView raise.
       
   384 
       
   385     layout := (actionData object) bounds asLayout.
       
   386     (actionData object) geometryLayout:layout.
       
   387 
       
   388     self changed:#tree.
       
   389     self select:(actionData object).
       
   390     actionData := nil.
       
   391 
       
   392     self setDefaultActions.
       
   393 
       
   394 !
       
   395 
       
   396 setupCreatedObject:anObject
       
   397     self subclassResponsibility
       
   398 !
       
   399 
       
   400 startCreate:aPoint
       
   401     "start a widget create
       
   402     "
       
   403     |widget object start frame delta|
       
   404 
       
   405     (createClass isNil or:[self numberOfSelections > 1]) ifTrue:[
       
   406         self unselect.
       
   407       ^ self setDefaultActions.
       
   408     ].
       
   409 
       
   410     motionAction  := [:movePoint| self doDragCreate:movePoint].
       
   411     releaseAction := [ self endCreate].
       
   412 
       
   413     widget := self singleSelection.
       
   414 
       
   415     (     widget notNil
       
   416      and:[(self isPoint:aPoint containedIn:widget)
       
   417      and:[self supportsSubComponents:widget]]
       
   418     ) ifFalse:[
       
   419         self unselect.
       
   420         widget := self.
       
   421     ].
       
   422 
       
   423     object := createClass new.
       
   424     widget addSubView:object.
       
   425 
       
   426     start := self alignToGrid:aPoint.
       
   427     delta := widget originRelativeTo:self.
       
   428     frame := Rectangle origin:(start - delta) corner:start.
       
   429 
       
   430     object origin:(frame origin).
       
   431     self setupCreatedObject:object.
       
   432     object realize.
       
   433 
       
   434     self actionCreate:object frame:frame delta:delta.
       
   435     self invertOutlineOf:object.
       
   436 
       
   437 
       
   438 ! !
       
   439 
       
   440 !UIObjectView methodsFor:'object moving'!
       
   441 
       
   442 doObjectMove:aPoint
       
   443     "move selection
       
   444     "
       
   445     movedObject notNil ifTrue:[
       
   446         movedObject keysAndValuesDo:[:nr :aView|
       
   447             self invertOutlineOf:aView.
       
   448             self moveObject:aView to:(aPoint - (moveDelta at:nr)).
       
   449             self invertOutlineOf:aView.
       
   450         ]
       
   451     ]
       
   452 
       
   453 !
       
   454 
       
   455 endObjectMove
       
   456     "cleanup after object move"
       
   457 
       
   458     movedObject notNil ifTrue:[
       
   459         movedObject do:[:aView|
       
   460             self invertOutlineOf:aView
       
   461         ].
       
   462 
       
   463         movedObject do:[:aView|
       
   464             self showSelected:aView
       
   465         ].
       
   466         movedObject size == 1 ifTrue:[
       
   467             selection := movedObject at:1
       
   468         ] ifFalse:[
       
   469             selection := movedObject
       
   470         ].
       
   471 
       
   472         movedObject := nil.
       
   473         self setDefaultActions.
       
   474         self changed:#layout.
       
   475     ].
       
   476 !
       
   477 
       
   478 moveObject:anObject to:aPoint
       
   479     "move anObject to newOrigin, aPoint
       
   480     "
       
   481     |dX dY org delta|
       
   482 
       
   483     anObject notNil ifTrue:[
       
   484         org := anObject computeOrigin.
       
   485 
       
   486         delta := aPoint - org.
       
   487         delta := (self alignToGrid:aPoint) - org.
       
   488         dX := delta x.
       
   489         dY := delta y.
       
   490 
       
   491         undoHistory disabledTransitionDo:[
       
   492             self shiftLayout:anObject top:dY bottom:dY left:dX right:dX
       
   493         ]
       
   494     ]
       
   495 
       
   496 !
       
   497 
       
   498 startObjectMoveAt:aPoint
       
   499 
       
   500     self startObjectMove:selection at:aPoint.
       
   501 
       
   502     selection isCollection ifTrue:[
       
   503         movedObject := selection
       
   504     ] ifFalse:[
       
   505         movedObject := Array with:selection
       
   506     ].
       
   507     super unselect.
       
   508 
       
   509     moveDelta := movedObject collect:[:aView|
       
   510         aPoint - aView computeOrigin
       
   511     ].
       
   512 
       
   513     self transaction:#move objects:movedObject do:[:aView|
       
   514         self invertOutlineOf:aView.
       
   515         self undoBlockPositionChanged:aView
       
   516     ].
       
   517 
       
   518 !
       
   519 
       
   520 startSelectMoreOrMove:aPoint
       
   521     "add/remove to/from selection"
       
   522 
       
   523     |anObject|
       
   524 
       
   525     testMode ifTrue:[^ self].
       
   526 
       
   527     anObject := self findObjectAt:aPoint.
       
   528     anObject notNil ifTrue:[
       
   529         (self isSelected:anObject) ifTrue:[
       
   530             self removeFromSelection:anObject
       
   531         ] ifFalse:[
       
   532             self addToSelection:anObject
       
   533         ]
       
   534     ]
       
   535 !
       
   536 
       
   537 startSelectOrMove:aPoint
       
   538     "a button is pressed at a point
       
   539     "
       
   540     |anObject b|
       
   541 
       
   542     testMode ifTrue:[^ self].
       
   543 
       
   544     "if there is one object selected and point hits a handle, start a resize
       
   545     "
       
   546     anObject := self singleSelection.
       
   547 
       
   548     anObject notNil ifTrue:[
       
   549         b := self whichHandleOf:anObject isHitBy:aPoint.
       
   550 
       
   551         (b notNil and:[b ~~ #view]) ifTrue:[
       
   552             ^ self startResizeBorder:b of:anObject.
       
   553         ]
       
   554     ].
       
   555 
       
   556     anObject := self findObjectAt:aPoint.
       
   557 
       
   558     "nothing is selected
       
   559     "
       
   560     anObject isNil ifTrue:[
       
   561         ^ self unselect
       
   562     ].
       
   563 
       
   564     (self isSelected:anObject) ifFalse:[
       
   565         super unselect.
       
   566         self select:anObject.
       
   567     ].
       
   568 
       
   569     (self numberOfSelections ~~ 1) ifTrue:[
       
   570         releaseAction := [
       
   571             self setDefaultActions.
       
   572             self select:anObject
       
   573         ]
       
   574     ] ifFalse:[
       
   575         releaseAction := [self setDefaultActions]
       
   576     ].
       
   577 
       
   578     "prepare move operation for an object
       
   579     "
       
   580     motionAction := [:movePoint|
       
   581         (aPoint dist:movePoint) > 4.0 ifTrue:[
       
   582             self startObjectMoveAt:aPoint
       
   583         ]
       
   584     ].
       
   585 ! !
       
   586 
       
   587 !UIObjectView methodsFor:'object resize'!
       
   588 
       
   589 actionResize:anObject selector:aSelector
       
   590     "create and initialize action for resize
       
   591     "
       
   592     |selector delta|
       
   593 
       
   594     delta    := anObject container originRelativeTo:self.
       
   595     selector := ('resize:', aSelector, ':') asSymbol.
       
   596 
       
   597     actionData := Structure with:(#object->anObject)
       
   598                             with:(#selector->selector)
       
   599                             with:(#delta->delta).
       
   600 
       
   601 "can change cursor dependent on vertical/horizontal resizing
       
   602 "
       
   603     oldCursor := cursor.
       
   604     self cursor:(Cursor leftHand).
       
   605 
       
   606 
       
   607 
       
   608 !
       
   609 
       
   610 doDragResize:aPoint
       
   611     "do a widget resize drag"
       
   612 
       
   613     |p object|
       
   614 
       
   615     object := actionData object.
       
   616 
       
   617     self invertOutlineOf:object.
       
   618     p := (self alignToGrid:aPoint) - (actionData delta).
       
   619     self perform:(actionData selector) with:object with:p.
       
   620     object geometryLayout:(object geometryLayout).
       
   621     self invertOutlineOf:object
       
   622 
       
   623 !
       
   624 
       
   625 endResize
       
   626     "cleanup after object resize"
       
   627 
       
   628     self invertOutlineOf:(actionData object).
       
   629     self setDefaultActions.
       
   630     self select:(actionData object).
       
   631     actionData := nil
       
   632 
       
   633     "Modified: 5.9.1995 / 17:11:17 / claus"
       
   634 
       
   635 !
       
   636 
       
   637 startResizeBorder:b of:selection
       
   638     "resize selected view
       
   639     "
       
   640     |object|
       
   641 
       
   642     object := self singleSelection.
       
   643 
       
   644     (object geometryLayout) isNil ifTrue:[
       
   645         ^ self setDefaultActions.
       
   646     ].
       
   647 
       
   648     self actionResize:object selector:b.
       
   649 
       
   650     self transaction:#extent selectionDo:[:aView|
       
   651         self undoBlockDimensionChanged:aView
       
   652     ].
       
   653     super unselect.
       
   654 
       
   655     motionAction  := [:movePoint | self doDragResize:movePoint].
       
   656     releaseAction := [self endResize].
       
   657     self invertOutlineOf:object
       
   658 ! !
       
   659 
       
   660 !UIObjectView methodsFor:'private handles'!
       
   661 
       
   662 handlesOf:aComponent do:aBlock
       
   663     |delta layout vertical horizontal|
       
   664 
       
   665     layout := aComponent geometryLayout.
       
   666     delta  := (aComponent originRelativeTo:self) - aComponent origin.
       
   667 
       
   668     (layout isLayout not or:[layout isLayoutFrame]) ifTrue:[
       
   669         vertical   := self isVerticalResizable:aComponent.
       
   670         horizontal := self isHorizontalResizable:aComponent.
       
   671     ] ifFalse:[
       
   672         vertical   := false.
       
   673         horizontal := false.
       
   674     ].
       
   675 
       
   676     horizontal ifTrue:[
       
   677         aBlock value:(aComponent leftCenter   + delta) value:#left.
       
   678         aBlock value:(aComponent rightCenter  + delta) value:#right.
       
   679     ].
       
   680 
       
   681     vertical ifTrue:[
       
   682         aBlock value:(aComponent topCenter    + delta) value:#top.
       
   683         aBlock value:(aComponent bottomCenter + delta) value:#bottom.
       
   684     ].
       
   685 
       
   686     (horizontal and:[vertical]) ifTrue:[
       
   687         aBlock value:(aComponent origin     + delta) value:#origin.
       
   688         aBlock value:(aComponent corner     + delta) value:#corner.
       
   689         aBlock value:(aComponent topRight   + delta) value:#topRight.
       
   690         aBlock value:(aComponent bottomLeft + delta) value:#bottomLeft.
       
   691     ] ifFalse:[
       
   692         aBlock value:(aComponent origin     + delta) value:#view.
       
   693         aBlock value:(aComponent corner     + delta) value:#view.
       
   694         aBlock value:(aComponent topRight   + delta) value:#view.
       
   695         aBlock value:(aComponent bottomLeft + delta) value:#view.
       
   696     ].
       
   697 
       
   698 !
       
   699 
       
   700 showSelected:aComponent
       
   701     |wasClipped delta oldPaint|
       
   702 
       
   703     self paint:Color black.
       
   704 
       
   705     (wasClipped := clipChildren) ifTrue:[
       
   706         self clippedByChildren:(clipChildren := false). 
       
   707     ].
       
   708 
       
   709     self handlesOf:aComponent do:[:pnt :what |
       
   710         what == #view ifTrue:[self displayRectangle:(pnt - (4@4) extent:7@7)]
       
   711                      ifFalse:[self    fillRectangle:(pnt - (4@4) extent:7@7)]
       
   712     ].
       
   713 
       
   714     wasClipped ifTrue:[
       
   715         self clippedByChildren:(clipChildren := true).
       
   716     ].
       
   717     self paint:oldPaint.
       
   718 !
       
   719 
       
   720 showUnselected:aComponent
       
   721     |wasClipped delta r oldPaint|
       
   722 
       
   723     r := aComponent origin extent:8@8.
       
   724 
       
   725     (wasClipped := clipChildren) ifTrue:[
       
   726         self clippedByChildren:(clipChildren := false). 
       
   727     ].
       
   728 
       
   729     self handlesOf:aComponent do:[:pnt :what |
       
   730         self clearRectangle:(pnt - (4@4) extent:7@7).
       
   731     ].
       
   732 
       
   733     wasClipped ifTrue:[
       
   734         self clippedByChildren:(clipChildren := true). 
       
   735     ].
       
   736 
       
   737     "/ must redraw all components which are affected b the handles
       
   738 
       
   739     r := (aComponent originRelativeTo:self) - (4@4)
       
   740              extent:(aComponent extent + (4@4)).
       
   741 
       
   742     subViews do:[:anotherComponent |
       
   743         |absOrg absFrame|
       
   744 
       
   745         anotherComponent ~~ inputView ifTrue:[
       
   746             absOrg := anotherComponent originRelativeTo:self.
       
   747             absFrame := absOrg extent:(anotherComponent extent).
       
   748             (absFrame intersects:r) ifTrue:[
       
   749                 anotherComponent withAllSubViewsDo:[:v |
       
   750                     v clear.
       
   751                     v exposeX:0 y:0 width:9999 height:9999.
       
   752                 ]
       
   753             ]
       
   754         ]
       
   755     ]
       
   756 
       
   757 !
       
   758 
       
   759 whichHandleOf:aView isHitBy:aPoint
       
   760     |bounds|
       
   761 
       
   762     self handlesOf:aView do:[:pnt :what |
       
   763         ((pnt - (4@4) extent:7@7) containsPoint:aPoint) ifTrue:[
       
   764             ^ what
       
   765         ].
       
   766     ].
       
   767 
       
   768     ^ nil
       
   769 
       
   770     "Modified: 5.9.1995 / 14:39:34 / claus"
       
   771 
       
   772 ! !
       
   773 
       
   774 !UIObjectView methodsFor:'private resizing-subviews'!
       
   775 
       
   776 resize:aView bottom:aPoint
       
   777 
       
   778     undoHistory disabledTransitionDo:[
       
   779         self shiftLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
       
   780     ]
       
   781 !
       
   782 
       
   783 resize:aView bottomLeft:aPoint
       
   784 
       
   785     undoHistory disabledTransitionDo:[
       
   786         self shiftLayout:aView top:0
       
   787                             bottom:((aPoint y) - (aView computeCorner y))
       
   788                               left:((aPoint x) - (aView computeOrigin x))
       
   789                              right:0
       
   790 
       
   791     ]
       
   792 
       
   793 
       
   794 !
       
   795 
       
   796 resize:aView corner:aPoint
       
   797     |delta|
       
   798 
       
   799     delta := aPoint - aView computeCorner.
       
   800 
       
   801     undoHistory disabledTransitionDo:[
       
   802         self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
       
   803     ]
       
   804 !
       
   805 
       
   806 resize:aView left:aPoint
       
   807 
       
   808     undoHistory disabledTransitionDo:[
       
   809         self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
       
   810     ]
       
   811 
       
   812 !
       
   813 
       
   814 resize:aView origin:aPoint
       
   815     |delta|
       
   816 
       
   817     delta := aPoint - aView computeOrigin.
       
   818 
       
   819     undoHistory disabledTransitionDo:[
       
   820         self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
       
   821     ]
       
   822 
       
   823 !
       
   824 
       
   825 resize:aView right:aPoint
       
   826 
       
   827     undoHistory disabledTransitionDo:[
       
   828         self shiftLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
       
   829     ]
       
   830 !
       
   831 
       
   832 resize:aView top:aPoint
       
   833 
       
   834     undoHistory disabledTransitionDo:[
       
   835         self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y)) bottom:0
       
   836     ]
       
   837 !
       
   838 
       
   839 resize:aView topRight:aPoint
       
   840 
       
   841     undoHistory disabledTransitionDo:[
       
   842         self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y))
       
   843                             bottom:0
       
   844                               left:0
       
   845                              right:((aPoint x) - (aView computeCorner x))
       
   846 
       
   847     ]
       
   848 
       
   849 ! !
       
   850 
       
   851 !UIObjectView methodsFor:'private shift-layout'!
       
   852 
       
   853 shiftLayout:aView left:l right:r
       
   854     "shift layout for a view; in case of an open transaction, the undo
       
   855      action is registered
       
   856     "
       
   857     self shiftLayout:aView top:0 bottom:0 left:l right:r
       
   858 
       
   859 !
       
   860 
       
   861 shiftLayout:aView top:t bottom:b
       
   862     "shift layout for a view; in case of an open transaction, the undo
       
   863      action is registered
       
   864     "
       
   865     self shiftLayout:aView top:t bottom:b left:0 right:0
       
   866 
       
   867 
       
   868 !
       
   869 
       
   870 shiftLayout:aView top:t bottom:b left:l right:r
       
   871     "shift layout for a view; in case of an open transaction, the undo
       
   872      action is registered
       
   873     "
       
   874     |layout|
       
   875 
       
   876     layout := aView geometryLayout.
       
   877 
       
   878     layout isLayout ifTrue:[
       
   879         self undoBlockPositionChanged:aView.
       
   880 
       
   881         layout leftOffset:(layout leftOffset + l)
       
   882                 topOffset:(layout topOffset  + t).
       
   883 
       
   884         layout isLayoutFrame ifTrue:[
       
   885             layout bottomOffset:(layout bottomOffset + b).
       
   886             layout  rightOffset:(layout rightOffset  + r).
       
   887         ].
       
   888         aView geometryLayout:layout.
       
   889     ] ifFalse:[
       
   890         |pixelOrigin|
       
   891 
       
   892         self undoBlockPositionChanged:aView.
       
   893 
       
   894         pixelOrigin := aView pixelOrigin.
       
   895         pixelOrigin := pixelOrigin + (l@t).
       
   896         aView pixelOrigin:pixelOrigin
       
   897     ]
       
   898 
       
   899 
       
   900 ! !
       
   901 
       
   902 !UIObjectView methodsFor:'searching'!
       
   903 
       
   904 findObjectAt:aPoint
       
   905     "find the origin/corner of the currentWidget
       
   906     "
       
   907     |view viewId lastId point|
       
   908 
       
   909     viewId := rootView id.
       
   910     point  := aPoint + (device translatePoint:0@0 from:(self id) to:viewId).
       
   911 
       
   912     inputView lower.
       
   913 
       
   914     [viewId notNil] whileTrue:[
       
   915         lastId := viewId.
       
   916         viewId := device viewIdFromPoint:point in:lastId
       
   917     ].
       
   918 
       
   919     inputView raise.
       
   920 
       
   921     view := device viewFromId:lastId.
       
   922 
       
   923     view ~~ inputView ifTrue:[^ view]
       
   924                      ifFalse:[^ nil]
       
   925 
       
   926 
       
   927 !
       
   928 
       
   929 isPoint:aPoint containedIn:aView
       
   930     "checks whether a point is covered by a view.
       
   931     "
       
   932     |p|
       
   933 
       
   934     p := device translatePoint:aPoint from:inputView id to:aView id.
       
   935 
       
   936     (p x >= 0 and:[p y >= 0]) ifTrue:[
       
   937         p := aView extent - p.
       
   938 
       
   939         (p x >= 0 and:[p y >= 0]) ifTrue:[
       
   940             ^ true
       
   941         ]
       
   942     ].
       
   943     ^ false
       
   944 !
       
   945 
       
   946 whichBorderOf:aView isHitBy:aPoint
       
   947     |p r bw org|
       
   948 
       
   949     bw := aView borderWidth.
       
   950     p := aPoint - (aView superView originRelativeTo:self).
       
   951 
       
   952     r := Rectangle origin:(aView origin)
       
   953                    extent:(aView width @ bw).
       
   954     (r containsPoint:p) ifTrue:[^ #top:].
       
   955 
       
   956     r origin:(aView left @ (aView bottom + bw)) extent:(aView width @ bw).
       
   957     (r containsPoint:p) ifTrue:[^ #bottom:].
       
   958 
       
   959     r top:(aView top).
       
   960     r extent:(bw @ aView height).
       
   961     (r containsPoint:p) ifTrue:[^ #left:].
       
   962 
       
   963     r origin:((aView right + bw) @ aView top).
       
   964     (r containsPoint:p) ifTrue:[^ #right:].
       
   965 
       
   966     ^ nil
       
   967 
       
   968 
       
   969 ! !
       
   970 
       
   971 !UIObjectView methodsFor:'selections'!
       
   972 
       
   973 addToSelection:something
       
   974     (self canSelect:something) ifTrue:[
       
   975         super addToSelection:something.
       
   976         self changed:#selection.
       
   977     ]
       
   978 !
       
   979 
       
   980 inspectSelection
       
   981     self singleSelectionDo:[:aView |
       
   982         aView inspect
       
   983     ]
       
   984 !
       
   985 
       
   986 numberOfSelections
       
   987     "return the number of selected entries"
       
   988 
       
   989     |sz|
       
   990 
       
   991     selection isNil ifTrue:[^ 0].
       
   992 
       
   993     selection isCollection ifTrue:[^ selection size]
       
   994                           ifFalse:[^ 1 ]
       
   995 !
       
   996 
       
   997 removeFromSelection:something
       
   998     super removeFromSelection:something.
       
   999     self changed:#selection
       
  1000 
       
  1001 !
       
  1002 
       
  1003 select:something
       
  1004     (self canSelect:something) ifTrue:[
       
  1005         super select:something.
       
  1006         self changed:#selection
       
  1007     ]
       
  1008 
       
  1009 !
       
  1010 
       
  1011 selection
       
  1012     ^ selection
       
  1013 
       
  1014 
       
  1015 !
       
  1016 
       
  1017 selectionHiddenDo:aBlock
       
  1018     "apply block to every object in selection"
       
  1019 
       
  1020     self selectionDo:[:aView |
       
  1021         self showUnselected:aView.
       
  1022     ].
       
  1023     device flush.
       
  1024     aBlock value.
       
  1025     self selectionDo:[:aView |
       
  1026         self showSelected:aView
       
  1027     ]
       
  1028 
       
  1029 
       
  1030 !
       
  1031 
       
  1032 singleSelection
       
  1033     "returns single selection or nil
       
  1034     "
       
  1035     selection isCollection ifFalse:[
       
  1036         ^ selection
       
  1037     ].
       
  1038     selection size == 1 ifTrue:[ ^ selection at:1]
       
  1039                        ifFalse:[ ^ nil].
       
  1040 !
       
  1041 
       
  1042 singleSelectionDo:aBlock
       
  1043     |view|
       
  1044 
       
  1045     (view := self singleSelection) notNil ifTrue:[
       
  1046         aBlock value:view
       
  1047     ]
       
  1048 !
       
  1049 
       
  1050 unselect
       
  1051     selection notNil ifTrue:[
       
  1052         super unselect.
       
  1053         self changed:#selection
       
  1054     ]
       
  1055 
       
  1056 !
       
  1057 
       
  1058 withSelectionHiddenDo:aBlock
       
  1059     "evaluate aBlock while selection is hidden"
       
  1060 
       
  1061     |sel|
       
  1062 
       
  1063     selection isNil ifTrue:[
       
  1064         aBlock value
       
  1065     ] ifFalse:[
       
  1066         sel := selection.
       
  1067         super unselect.
       
  1068         aBlock value.
       
  1069         super select:sel
       
  1070     ]
       
  1071 
       
  1072     "Modified: 6.9.1995 / 01:46:16 / claus"
       
  1073 
       
  1074 
       
  1075 ! !
       
  1076 
       
  1077 !UIObjectView methodsFor:'testing'!
       
  1078 
       
  1079 canMove:something
       
  1080     ^ true
       
  1081 
       
  1082 
       
  1083 !
       
  1084 
       
  1085 canPaste:something
       
  1086     "returns true if something could be paste
       
  1087     "
       
  1088     something notNil ifTrue:[
       
  1089         something isCollection ifTrue:[
       
  1090             something notEmpty ifTrue:[
       
  1091                 ^ (something at:1) isKindOf:UISpecification
       
  1092             ]
       
  1093         ] ifFalse:[
       
  1094             ^ something isKindOf:UISpecification
       
  1095         ]
       
  1096     ].
       
  1097     ^ false
       
  1098 
       
  1099 !
       
  1100 
       
  1101 canSelect:something
       
  1102     ^ (testMode not and:[something ~~ selection])
       
  1103 
       
  1104 !
       
  1105 
       
  1106 hasUndos
       
  1107     "returns true if undoHistory not empty
       
  1108     "
       
  1109     ^ undoHistory notEmpty
       
  1110 !
       
  1111 
       
  1112 isHorizontalResizable:aComponent
       
  1113     ^ self subclassResponsibility
       
  1114 
       
  1115 
       
  1116 !
       
  1117 
       
  1118 isVerticalResizable:aComponent
       
  1119     ^ self subclassResponsibility
       
  1120 
       
  1121 
       
  1122 !
       
  1123 
       
  1124 supportsSubComponents:something
       
  1125     "returns true if somrthing supports subcomponents
       
  1126     "
       
  1127     |specClass|
       
  1128 
       
  1129     something notNil ifTrue:[
       
  1130         something isCollection ifFalse:[
       
  1131             specClass := something specClass
       
  1132         ] ifTrue:[
       
  1133             something size == 1 ifTrue:[
       
  1134                 specClass := (something at:1) specClass
       
  1135             ]
       
  1136         ].
       
  1137         specClass notNil ifTrue:[
       
  1138             ^ specClass basicNew supportsSubComponents
       
  1139         ]
       
  1140     ].
       
  1141     ^ false
       
  1142 ! !
       
  1143 
       
  1144 !UIObjectView methodsFor:'transaction & undo'!
       
  1145 
       
  1146 transaction:aType objects:something do:aOneArgBlock
       
  1147     "opens a transaction and evaluates a block within the transaction; the
       
  1148      argument to the block is a view from derived from something
       
  1149     "
       
  1150     self subclassResponsibility
       
  1151 
       
  1152 
       
  1153 !
       
  1154 
       
  1155 transaction:aType selectionDo:aOneArgBlock
       
  1156     "opens a transaction and evaluates a block within the transaction; the
       
  1157      argument to the block is a view from the selection
       
  1158     "
       
  1159     self transaction:aType objects:selection do:aOneArgBlock
       
  1160 
       
  1161 
       
  1162 !
       
  1163 
       
  1164 undoBlockDimensionChanged:aView
       
  1165 
       
  1166     undoHistory isTransactionOpen ifTrue:[
       
  1167         |layout|
       
  1168 
       
  1169         layout := aView geometryLayout copy.
       
  1170 
       
  1171         undoHistory addUndoBlock:[
       
  1172             aView geometryLayout:layout.
       
  1173             aView superView sizeChanged:nil.
       
  1174         ]
       
  1175     ]
       
  1176 
       
  1177 !
       
  1178 
       
  1179 undoBlockPositionChanged:aView
       
  1180 
       
  1181     undoHistory isTransactionOpen ifTrue:[
       
  1182         |layout|
       
  1183 
       
  1184         layout := aView geometryLayout copy.
       
  1185         layout isNil ifFalse:[
       
  1186             undoHistory addUndoBlock:[aView geometryLayout:layout]
       
  1187         ] ifTrue:[
       
  1188             layout := aView pixelOrigin.
       
  1189             undoHistory addUndoBlock:[aView pixelOrigin:layout]
       
  1190         ]
       
  1191     ]
       
  1192 
       
  1193 !
       
  1194 
       
  1195 undoDeleteAll
       
  1196     "delete total undo history
       
  1197     "
       
  1198     undoHistory reinitialize
       
  1199 !
       
  1200 
       
  1201 undoLast
       
  1202     self undoLast:1
       
  1203 !
       
  1204 
       
  1205 undoLast:n
       
  1206 
       
  1207     self unselect.
       
  1208     undoHistory undoLast:n.
       
  1209     self changed:#tree
       
  1210 
       
  1211 
       
  1212 ! !
       
  1213 
       
  1214 !UIObjectView methodsFor:'user actions - dimension'!
       
  1215 
       
  1216 copyExtent
       
  1217     |object|
       
  1218 
       
  1219     object := self singleSelection.
       
  1220 
       
  1221     object notNil ifTrue:[
       
  1222         copiedExtent := object computeExtent
       
  1223     ] ifFalse:[
       
  1224         self warn:'exactly one element must be selected'.
       
  1225     ]
       
  1226 
       
  1227 
       
  1228 
       
  1229 !
       
  1230 
       
  1231 pasteExtent
       
  1232     copiedExtent notNil ifTrue:[
       
  1233         self transition:#extent dimensionDo:[:v|
       
  1234             self resize:v corner:(v computeOrigin + copiedExtent)
       
  1235         ]    
       
  1236     ]    
       
  1237 !
       
  1238 
       
  1239 pasteHeight
       
  1240     copiedExtent notNil ifTrue:[
       
  1241         self transition:'paste height' dimensionDo:[:v|
       
  1242             self resize:v bottom:(v computeOrigin + copiedExtent)
       
  1243         ]    
       
  1244     ]    
       
  1245 
       
  1246 !
       
  1247 
       
  1248 pasteWidth
       
  1249     copiedExtent notNil ifTrue:[
       
  1250         self transition:'paste width' dimensionDo:[:v|
       
  1251             self resize:v right:(v computeOrigin + copiedExtent)
       
  1252         ]    
       
  1253     ]    
       
  1254 
       
  1255 !
       
  1256 
       
  1257 setDimension:aLayout
       
  1258     |type|
       
  1259 
       
  1260     aLayout isLayout ifTrue:[
       
  1261         aLayout isLayoutFrame ifTrue:[
       
  1262             type := #layoutFrame
       
  1263         ] ifFalse:[
       
  1264             aLayout isAlignmentOrigin ifTrue:[
       
  1265                 type := #layoutAlignOrigin.
       
  1266             ] ifFalse:[
       
  1267                 type := #layoutOrigin
       
  1268             ]
       
  1269         ]
       
  1270     ] ifFalse:[
       
  1271         type := #layout
       
  1272     ].
       
  1273 
       
  1274     self transition:type dimensionDo:[:v| v geometryLayout:(aLayout copy)]    
       
  1275 
       
  1276 !
       
  1277 
       
  1278 setToDefaultExtent
       
  1279     self transition:#extent dimensionDo:[:v|
       
  1280         self resize:v corner:(v computeOrigin + (v preferredExtent))
       
  1281     ]    
       
  1282 
       
  1283 !
       
  1284 
       
  1285 setToDefaultHeight
       
  1286     self transition:'default height' dimensionDo:[:v|
       
  1287         self resize:v bottom:(v computeOrigin + (v preferredExtent))
       
  1288     ]    
       
  1289 
       
  1290 !
       
  1291 
       
  1292 setToDefaultWidth
       
  1293     self transition:'default width' dimensionDo:[:v|
       
  1294         self resize:v right:(v computeOrigin + (v preferredExtent))
       
  1295     ]    
       
  1296 
       
  1297 !
       
  1298 
       
  1299 transition:aType dimensionDo:aOneArgBlock
       
  1300     "change dimension within a transaction for the selected elements by evaluating
       
  1301      the block with the argument a view.
       
  1302     "
       
  1303     self selectionHiddenDo:[
       
  1304         self transaction:aType selectionDo:[:aView|
       
  1305             self undoBlockDimensionChanged:aView.
       
  1306             aOneArgBlock value:aView.
       
  1307             aView superView sizeChanged:nil
       
  1308         ].
       
  1309         self changed:#layout
       
  1310     ]
       
  1311 ! !
       
  1312 
       
  1313 !UIObjectView methodsFor:'user actions - move'!
       
  1314 
       
  1315 moveSelectionDown:aNumber
       
  1316     |gridY|
       
  1317 
       
  1318     gridAlign notNil ifTrue:[
       
  1319         gridY := gridAlign y.
       
  1320     ].
       
  1321 
       
  1322     self selectionHiddenDo:[
       
  1323         self transaction:#move selectionDo:[:aView|
       
  1324             |n d|
       
  1325 
       
  1326             n := aNumber.
       
  1327 
       
  1328             aligning ifTrue:[
       
  1329                 d := ((aView computeCorner y) \\ gridY).
       
  1330                 n := n * gridY.
       
  1331 
       
  1332                 d ~~ 0 ifTrue:[
       
  1333                     n := n - d + 1.
       
  1334                 ]
       
  1335             ].
       
  1336             self shiftLayout:aView top:n bottom:n
       
  1337         ].
       
  1338         self changed:#layout
       
  1339     ]
       
  1340 
       
  1341 
       
  1342 !
       
  1343 
       
  1344 moveSelectionLeft:aNumber
       
  1345     "move selection left
       
  1346     "
       
  1347     |gridX|
       
  1348 
       
  1349     gridAlign notNil ifTrue:[
       
  1350         gridX := gridAlign x.
       
  1351     ].
       
  1352 
       
  1353     self selectionHiddenDo:[
       
  1354         self transaction:#move selectionDo:[:aView|
       
  1355             |n d|
       
  1356 
       
  1357             n := aNumber.
       
  1358 
       
  1359             aligning ifTrue:[
       
  1360                 d := ((aView computeOrigin x) \\ gridX).
       
  1361                 d ~~ 0 ifTrue:[
       
  1362                     n := n-1.
       
  1363                 ].
       
  1364                 n := (n * gridX) + d.
       
  1365             ].
       
  1366             n := n negated.
       
  1367             self shiftLayout:aView left:n right:n
       
  1368 
       
  1369         ].
       
  1370         self changed:#layout
       
  1371     ]
       
  1372 !
       
  1373 
       
  1374 moveSelectionRight:aNumber
       
  1375     "move selection right
       
  1376     "
       
  1377     |gridX|
       
  1378 
       
  1379     gridAlign notNil ifTrue:[
       
  1380         gridX := gridAlign x.
       
  1381     ].
       
  1382 
       
  1383     self selectionHiddenDo:[
       
  1384         self transaction:#move selectionDo:[:aView|
       
  1385             |n d|
       
  1386 
       
  1387             n := aNumber.
       
  1388 
       
  1389             aligning ifTrue:[
       
  1390                 d := ((aView computeCorner x) \\ gridX).
       
  1391                 n := n * gridX.
       
  1392 
       
  1393                 d ~~ 0 ifTrue:[
       
  1394                     n := n - d + 1.
       
  1395                 ]
       
  1396             ].
       
  1397             self shiftLayout:aView left:n right:n
       
  1398 
       
  1399         ].
       
  1400         self changed:#layout
       
  1401     ]
       
  1402 !
       
  1403 
       
  1404 moveSelectionUp:aNumber
       
  1405     "move selection up
       
  1406     "
       
  1407     |gridY|
       
  1408 
       
  1409     gridAlign notNil ifTrue:[
       
  1410         gridY := gridAlign y.
       
  1411     ].
       
  1412 
       
  1413     self selectionHiddenDo:[
       
  1414         self transaction:#move selectionDo:[:aView|
       
  1415             |n d|
       
  1416 
       
  1417             n := aNumber.
       
  1418 
       
  1419             aligning ifTrue:[
       
  1420                 d := ((aView computeOrigin x) \\ gridY).
       
  1421                 d ~~ 0 ifTrue:[
       
  1422                     n := n-1.
       
  1423                 ].
       
  1424                 n := (n * gridY) + d.
       
  1425             ].
       
  1426             n := n negated.
       
  1427             self shiftLayout:aView top:n bottom:n
       
  1428         ].
       
  1429         self changed:#layout
       
  1430     ]
       
  1431 
       
  1432 
       
  1433 ! !
       
  1434 
       
  1435 !UIObjectView methodsFor:'user actions - position'!
       
  1436 
       
  1437 alignSelectionBottom
       
  1438     |bmost delta layout|
       
  1439 
       
  1440     selection notNil ifTrue:[
       
  1441         self selectionHiddenDo:[
       
  1442             self numberOfSelections > 1 ifTrue:[
       
  1443                 bmost := (selection at:1) computeCorner y.
       
  1444 
       
  1445                 self transaction:#align selectionDo:[:v|
       
  1446                     (delta := bmost - (v computeCorner y)) ~~ 0 ifTrue:[
       
  1447                         self shiftLayout:v top:delta bottom:delta.
       
  1448                     ]
       
  1449                 ]
       
  1450             ] ifFalse:[
       
  1451                 layout := selection geometryLayout.
       
  1452 
       
  1453                 (layout isLayout and:[layout isLayoutFrame]) ifFalse:[
       
  1454                     ^ self
       
  1455                 ].
       
  1456 
       
  1457                 self transaction:#layout selectionDo:[:aView|
       
  1458                     self undoBlockDimensionChanged:aView.
       
  1459                     layout := aView geometryLayout.
       
  1460                     layout bottomOffset:0.
       
  1461                     layout bottomFraction:1.0.
       
  1462                     aView geometryLayout:layout.
       
  1463                 ]
       
  1464             ]
       
  1465         ].
       
  1466         self changed:#layout
       
  1467     ]
       
  1468 
       
  1469 
       
  1470 
       
  1471 !
       
  1472 
       
  1473 alignSelectionCenterHor
       
  1474     |view center|
       
  1475 
       
  1476     selection notNil ifTrue:[
       
  1477         self selectionHiddenDo:[
       
  1478             view := self singleSelection.
       
  1479 
       
  1480             view notNil ifTrue:[
       
  1481                 view   := view superView.
       
  1482                 center := view computeExtent
       
  1483             ] ifFalse:[
       
  1484                 view   := selection at:1.
       
  1485                 center := view computeCorner + view computeOrigin.
       
  1486             ].
       
  1487             center := center x // 2.
       
  1488 
       
  1489             self transaction:#align selectionDo:[:v|
       
  1490                 |newX oldX delta|
       
  1491 
       
  1492                 oldX  := v computeOrigin x.
       
  1493                 newX  := center - ((v computeCorner x - oldX) // 2).
       
  1494                 delta := newX - oldX.
       
  1495 
       
  1496                 self shiftLayout:v left:delta right:delta
       
  1497             ].
       
  1498             self changed:#layout
       
  1499         ]
       
  1500     ]
       
  1501 
       
  1502 
       
  1503 
       
  1504 !
       
  1505 
       
  1506 alignSelectionCenterVer
       
  1507     |view center|
       
  1508 
       
  1509     selection notNil ifTrue:[
       
  1510         self selectionHiddenDo:[
       
  1511             view := self singleSelection.
       
  1512 
       
  1513             view notNil ifTrue:[
       
  1514                 view   := view superView.
       
  1515                 center := view computeExtent
       
  1516             ] ifFalse:[
       
  1517                 view   := selection at:1.
       
  1518                 center := view computeCorner + view computeOrigin.
       
  1519             ].
       
  1520             center := center y // 2.
       
  1521 
       
  1522             self transaction:#align selectionDo:[:v|
       
  1523                 |newY oldY delta|
       
  1524 
       
  1525                 oldY  := v computeOrigin y.
       
  1526                 newY  := center - ((v computeCorner y - oldY) // 2).
       
  1527                 delta := newY - oldY.
       
  1528 
       
  1529                 self shiftLayout:v top:delta bottom:delta
       
  1530             ].
       
  1531             self changed:#layout
       
  1532         ]
       
  1533     ]
       
  1534 !
       
  1535 
       
  1536 alignSelectionLeft
       
  1537     |lmost delta layout|
       
  1538 
       
  1539     selection notNil ifTrue:[
       
  1540         self selectionHiddenDo:[
       
  1541             self numberOfSelections > 1 ifTrue:[
       
  1542                 lmost := (selection at:1) computeOrigin x.
       
  1543 
       
  1544                 self transaction:#align selectionDo:[:v|
       
  1545                     (delta := lmost - (v computeOrigin x)) ~~ 0 ifTrue:[
       
  1546                         self shiftLayout:v left:delta right:delta
       
  1547                     ]
       
  1548                 ]
       
  1549             ] ifFalse:[
       
  1550                 self transaction:#layout selectionDo:[:aView|
       
  1551                     layout := aView geometryLayout.
       
  1552 
       
  1553                     layout isLayout ifTrue:[
       
  1554                         self undoBlockDimensionChanged:aView.
       
  1555                         layout leftOffset:0.
       
  1556                         layout leftFraction:0.0.
       
  1557                         aView geometryLayout:layout.
       
  1558                     ]
       
  1559                 ]
       
  1560             ]
       
  1561         ].
       
  1562         self changed:#layout
       
  1563     ]
       
  1564 !
       
  1565 
       
  1566 alignSelectionLeftAndRight
       
  1567     |lmost rmost layout|
       
  1568 
       
  1569     selection notNil ifTrue:[
       
  1570         self selectionHiddenDo:[
       
  1571             self numberOfSelections > 1 ifTrue:[
       
  1572                 lmost := (selection at:1) computeOrigin x.
       
  1573                 rmost := (selection at:1) computeCorner x.
       
  1574 
       
  1575                 self transaction:#align selectionDo:[:v|
       
  1576                     self shiftLayout:v left:(lmost - (v computeOrigin x))
       
  1577                                      right:(rmost - (v computeCorner x))
       
  1578                 ]
       
  1579             ] ifFalse:[
       
  1580                 self transaction:#layout selectionDo:[:aView|
       
  1581                     layout := aView geometryLayout.
       
  1582 
       
  1583                     layout isLayout ifTrue:[
       
  1584                         self undoBlockDimensionChanged:aView.
       
  1585                         layout leftOffset:0.
       
  1586                         layout leftFraction:0.0.
       
  1587 
       
  1588                         (layout isLayout and:[layout isLayoutFrame]) ifTrue:[
       
  1589                             layout rightOffset:0.
       
  1590                             layout rightFraction:1.0.
       
  1591                         ].
       
  1592                         aView geometryLayout:layout.
       
  1593                     ]
       
  1594                 ]
       
  1595             ]
       
  1596         ].
       
  1597         self changed:#layout
       
  1598     ]
       
  1599 !
       
  1600 
       
  1601 alignSelectionRight
       
  1602     |rmost delta layout|
       
  1603 
       
  1604     selection notNil ifTrue:[
       
  1605         self selectionHiddenDo:[
       
  1606             self numberOfSelections > 1 ifTrue:[
       
  1607                 rmost := (selection at:1) computeCorner x.
       
  1608 
       
  1609                 self transaction:#align selectionDo:[:v|
       
  1610                     (delta := rmost - (v computeCorner x)) ~~ 0 ifTrue:[
       
  1611                         self shiftLayout:v left:delta right:delta
       
  1612                     ]
       
  1613                 ]
       
  1614             ] ifFalse:[
       
  1615                 layout := selection geometryLayout.
       
  1616 
       
  1617                 (layout isLayout and:[layout isLayoutFrame]) ifFalse:[
       
  1618                     ^ self
       
  1619                 ].
       
  1620 
       
  1621                 self transaction:#layout selectionDo:[:aView|
       
  1622                     self undoBlockDimensionChanged:aView.
       
  1623                     layout := aView geometryLayout.
       
  1624                     layout rightOffset:0.
       
  1625                     layout rightFraction:1.0.
       
  1626                     aView geometryLayout:layout.
       
  1627                 ]
       
  1628             ]
       
  1629         ].
       
  1630         self changed:#layout
       
  1631     ]
       
  1632 !
       
  1633 
       
  1634 alignSelectionTop
       
  1635     |tmost delta layout|
       
  1636 
       
  1637     selection notNil ifTrue:[
       
  1638         self selectionHiddenDo:[
       
  1639             self numberOfSelections > 1 ifTrue:[
       
  1640                 tmost := (selection at:1) computeOrigin y.
       
  1641 
       
  1642                 self transaction:#align selectionDo:[:v|
       
  1643                     (delta := tmost - (v computeOrigin y)) ~~ 0 ifTrue:[
       
  1644                         self shiftLayout:v top:delta bottom:delta
       
  1645                     ]
       
  1646                 ]
       
  1647             ] ifFalse:[
       
  1648                 self transaction:#layout selectionDo:[:aView|
       
  1649                     layout := aView geometryLayout.
       
  1650 
       
  1651                     layout isLayout ifTrue:[
       
  1652                         self undoBlockDimensionChanged:aView.
       
  1653                         layout topOffset:0.
       
  1654                         layout topFraction:0.0.
       
  1655                         aView geometryLayout:layout.
       
  1656                     ]
       
  1657                 ]
       
  1658             ]
       
  1659         ].
       
  1660         self changed:#layout
       
  1661     ]
       
  1662 
       
  1663 !
       
  1664 
       
  1665 alignSelectionTopAndBottom
       
  1666     |tmost bmost layout|
       
  1667 
       
  1668     selection notNil ifTrue:[
       
  1669         self selectionHiddenDo:[
       
  1670             self numberOfSelections > 1 ifTrue:[
       
  1671                 tmost := (selection at:1) computeOrigin y.
       
  1672                 bmost := (selection at:1) computeCorner y.
       
  1673 
       
  1674                 self transaction:#align selectionDo:[:v|
       
  1675                     self shiftLayout:v top:(tmost - (v computeOrigin y))
       
  1676                                     bottom:(bmost - (v computeCorner y))
       
  1677                 ]
       
  1678             ] ifFalse:[
       
  1679                 self transaction:#layout selectionDo:[:aView|
       
  1680                     layout := aView geometryLayout.
       
  1681 
       
  1682                     layout isLayout ifTrue:[
       
  1683                         self undoBlockDimensionChanged:aView.
       
  1684                         layout topOffset:0.
       
  1685                         layout topFraction:0.0.
       
  1686 
       
  1687                         (layout isLayout and:[layout isLayoutFrame]) ifTrue:[
       
  1688                             layout bottomOffset:0.
       
  1689                             layout bottomFraction:1.0.
       
  1690                         ].
       
  1691                         aView geometryLayout:layout.
       
  1692                     ]
       
  1693                 ]
       
  1694             ]
       
  1695         ].
       
  1696         self changed:#layout
       
  1697     ]
       
  1698 !
       
  1699 
       
  1700 centerSelection:aOneArgBlockXorY orientation:orientation
       
  1701     "center selection horizontal or vertical dependant on the block result( x or y).
       
  1702      The argument to the block is the point.
       
  1703     "
       
  1704     |superview min max delta val|
       
  1705 
       
  1706     self selectionHiddenDo:[
       
  1707         max := 0.
       
  1708 
       
  1709         self selectionDo:[:aView |
       
  1710             superview isNil ifTrue:[
       
  1711                 superview := aView superView
       
  1712             ] ifFalse:[
       
  1713                 (aView superView == superview) ifFalse:[
       
  1714                     ^ self notify:'views must have same superview'.
       
  1715                 ]
       
  1716             ].
       
  1717             val := aOneArgBlockXorY value:(aView computeOrigin).    
       
  1718 
       
  1719             min isNil ifTrue:[min := val]
       
  1720                      ifFalse:[min := min min:val].
       
  1721 
       
  1722             val := aOneArgBlockXorY value:(aView computeCorner).
       
  1723             max := max max:val.
       
  1724         ].
       
  1725 
       
  1726         val := aOneArgBlockXorY value:(superview computeExtent).
       
  1727         max := (min + val - max) // 2.
       
  1728 
       
  1729         max == min ifFalse:[
       
  1730             delta := max - min.
       
  1731 
       
  1732             self transaction:#center selectionDo:[:v|
       
  1733                 orientation == #y ifTrue:[
       
  1734                     self shiftLayout:v top:delta bottom:delta
       
  1735                 ] ifFalse:[
       
  1736                     self shiftLayout:v left:delta right:delta
       
  1737                 ]
       
  1738             ].
       
  1739             self changed:#layout
       
  1740         ]
       
  1741     ]
       
  1742 
       
  1743 
       
  1744 !
       
  1745 
       
  1746 centerSelectionHor
       
  1747     "center selection horizontal
       
  1748     "
       
  1749     self centerSelection:[:aPoint| aPoint x] orientation:#x
       
  1750 
       
  1751 
       
  1752 !
       
  1753 
       
  1754 centerSelectionVer
       
  1755     "center selection vertical
       
  1756     "
       
  1757     self centerSelection:[:aPoint| aPoint y] orientation:#y
       
  1758 !
       
  1759 
       
  1760 spreadSelectionHor
       
  1761     |sumWidths min max viewsInOrder topsInOrder count space|
       
  1762 
       
  1763     (self numberOfSelections > 1) ifFalse:[
       
  1764         ^ self
       
  1765     ].
       
  1766 
       
  1767     self selectionHiddenDo:[
       
  1768         count := 0.
       
  1769         sumWidths := 0.
       
  1770         max := 0.
       
  1771 
       
  1772         self selectionDo:[:aView |
       
  1773             sumWidths := sumWidths + aView width.
       
  1774 
       
  1775             min isNil ifTrue:[min := aView left]
       
  1776                      ifFalse:[min := min min:(aView left)].
       
  1777 
       
  1778             max := max max:(aView right).
       
  1779             count := count + 1
       
  1780         ].
       
  1781         viewsInOrder := Array withAll:selection.
       
  1782         topsInOrder  := viewsInOrder collect:[:aView | aView left].
       
  1783         topsInOrder sortWith:viewsInOrder.
       
  1784 
       
  1785         space := (((max - min) - sumWidths) / (count - 1)) rounded asInteger.
       
  1786 
       
  1787         self transaction:#spread objects:viewsInOrder do:[:aView|
       
  1788             |delta|
       
  1789 
       
  1790             delta := min - aView computeOrigin x.
       
  1791             self shiftLayout:aView left:delta right:delta.
       
  1792             min := min + aView computeExtent x + space
       
  1793         ].
       
  1794         self changed:#layout
       
  1795     ]
       
  1796 
       
  1797 !
       
  1798 
       
  1799 spreadSelectionVer
       
  1800     |sumHeights min max viewsInOrder topsInOrder count space|
       
  1801 
       
  1802     (self numberOfSelections > 1) ifFalse:[
       
  1803         ^ self
       
  1804     ].
       
  1805 
       
  1806     self selectionHiddenDo:[
       
  1807         count := 0.
       
  1808         sumHeights := 0.
       
  1809         max := 0.
       
  1810 
       
  1811         self selectionDo:[:aView |
       
  1812             sumHeights := sumHeights + aView height.
       
  1813 
       
  1814             min isNil ifTrue:[min := aView top]
       
  1815                      ifFalse:[min := min min:(aView top)].
       
  1816 
       
  1817             max   := max max:(aView bottom).
       
  1818             count := count + 1
       
  1819         ].
       
  1820         viewsInOrder := Array withAll:selection.
       
  1821         topsInOrder  := viewsInOrder collect:[:aView|aView top].
       
  1822         topsInOrder sortWith:viewsInOrder.
       
  1823 
       
  1824         space := (((max - min) - sumHeights) / (count - 1)) rounded asInteger.
       
  1825 
       
  1826         self transaction:#spread objects:viewsInOrder do:[:aView|
       
  1827             |delta|
       
  1828 
       
  1829             delta := min - aView computeOrigin y.
       
  1830             self shiftLayout:aView top:delta bottom:delta.
       
  1831             min := min + aView height + space
       
  1832         ].
       
  1833         self changed:#layout
       
  1834     ]
       
  1835 ! !
       
  1836 
       
  1837 !UIObjectView::UndoHistory class methodsFor:'constants'!
       
  1838 
       
  1839 maxHistorySize
       
  1840     "returns maximum size of history before removing oldest
       
  1841      record
       
  1842     "
       
  1843     ^ 50
       
  1844 
       
  1845 
       
  1846 ! !
       
  1847 
       
  1848 !UIObjectView::UndoHistory class methodsFor:'instance creation'!
       
  1849 
       
  1850 new
       
  1851     ^ self basicNew initialize
       
  1852 
       
  1853 
       
  1854 ! !
       
  1855 
       
  1856 !UIObjectView::UndoHistory methodsFor:'accessing'!
       
  1857 
       
  1858 historySize
       
  1859     ^ history size
       
  1860 ! !
       
  1861 
       
  1862 !UIObjectView::UndoHistory methodsFor:'initialization'!
       
  1863 
       
  1864 initialize
       
  1865     super initialize.
       
  1866     self  reinitialize.
       
  1867 
       
  1868 
       
  1869 !
       
  1870 
       
  1871 reinitialize
       
  1872     "reinitialize all attributes
       
  1873     "
       
  1874     history     := OrderedCollection new.
       
  1875     transaction := nil.
       
  1876     enabled     := true.
       
  1877 
       
  1878 
       
  1879 ! !
       
  1880 
       
  1881 !UIObjectView::UndoHistory methodsFor:'menu'!
       
  1882 
       
  1883 popupMenu
       
  1884     "returns a submenu for undo
       
  1885     "
       
  1886     |labels|
       
  1887 
       
  1888     labels := OrderedCollection new:(history size).
       
  1889     history reverseDo:[:aRecord| labels add:(aRecord asString) ].
       
  1890 
       
  1891     ^ PopUpMenu labels:labels selectors:#undoLast:.
       
  1892 
       
  1893 ! !
       
  1894 
       
  1895 !UIObjectView::UndoHistory methodsFor:'testing'!
       
  1896 
       
  1897 isEmpty
       
  1898     "returns true if undo history is empty
       
  1899     "
       
  1900     ^ history isEmpty
       
  1901 
       
  1902 
       
  1903 !
       
  1904 
       
  1905 isTransactionOpen
       
  1906     ^ (enabled and:[transaction notNil])
       
  1907 !
       
  1908 
       
  1909 notEmpty
       
  1910     "returns true if undo history is not empty
       
  1911     "
       
  1912     ^ history notEmpty
       
  1913 
       
  1914 
       
  1915 ! !
       
  1916 
       
  1917 !UIObjectView::UndoHistory methodsFor:'transaction'!
       
  1918 
       
  1919 addUndoBlock:anUndoBlock
       
  1920     "undo block to restore changes; add block to current transaction
       
  1921     "
       
  1922     self isTransactionOpen ifTrue:[
       
  1923         transaction add:anUndoBlock
       
  1924     ]
       
  1925 
       
  1926 
       
  1927 !
       
  1928 
       
  1929 disabledTransitionDo:aBlock
       
  1930     "disable transitions during evaluating the block
       
  1931     "
       
  1932     |oldState|
       
  1933 
       
  1934     oldState := enabled.
       
  1935     enabled  := false.
       
  1936     aBlock value.
       
  1937     enabled  := oldState.
       
  1938 !
       
  1939 
       
  1940 transaction:aType do:aBlock
       
  1941     self transaction:aType text:nil do:aBlock
       
  1942 !
       
  1943 
       
  1944 transaction:aType text:aTextOrNil do:aBlock
       
  1945     "open a transaction; perform the block; at least close the transaction
       
  1946     "
       
  1947     (enabled and:[transaction isNil]) ifTrue:[
       
  1948         transaction := Transaction type:aType text:aTextOrNil.
       
  1949 
       
  1950         aBlock value.
       
  1951 
       
  1952         transaction isEmpty ifFalse:[
       
  1953             history addLast:transaction.
       
  1954             history size > (self class maxHistorySize) ifTrue:[history removeFirst]
       
  1955         ].
       
  1956         transaction := nil
       
  1957 
       
  1958     ] ifFalse:[
       
  1959         aBlock value
       
  1960     ]
       
  1961 ! !
       
  1962 
       
  1963 !UIObjectView::UndoHistory methodsFor:'undo'!
       
  1964 
       
  1965 undoLast:nTransactions
       
  1966     "undo last n transactions; an open transaction will be closed;
       
  1967      transactions during undo are disabled
       
  1968     "
       
  1969     |n|
       
  1970 
       
  1971     transaction := nil.
       
  1972     n := nTransactions min:(history size).
       
  1973 
       
  1974     n ~~ 0 ifTrue:[
       
  1975         enabled := false.
       
  1976         n timesRepeat:[ (history removeLast) undo ].
       
  1977         enabled := true.
       
  1978     ]
       
  1979 
       
  1980 
       
  1981 ! !
       
  1982 
     7 
  1983 !UIObjectView::UndoHistory::Transaction class methodsFor:'instance creation'!
     8 !UIObjectView::UndoHistory::Transaction class methodsFor:'instance creation'!
  1984 
     9 
  1985 type:aType text:aTextOrNil
    10 type:aType text:aTextOrNil
  1986     ^ self new type:aType text:aTextOrNil
    11     ^ self new type:aType text:aTextOrNil
  1995     "
    20     "
  1996     |string|
    21     |string|
  1997 
    22 
  1998     string := type asString.
    23     string := type asString.
  1999 
    24 
  2000     text notNil ifTrue:[^ string, '  ', text ]
    25     text notNil ifTrue:[^ string, '    ', text ]
  2001                ifFalse:[^ string ]
    26                ifFalse:[^ string ]
  2002 !
    27 !
  2003 
    28 
  2004 text
    29 text
  2005     "returns text or nil assigned to transition
    30     "returns text or nil assigned to transition
  2071     "returns true if any undo action is registered
    96     "returns true if any undo action is registered
  2072     "
    97     "
  2073     ^ actions notNil
    98     ^ actions notNil
  2074 ! !
    99 ! !
  2075 
   100 
  2076 !UIObjectView class methodsFor:'documentation'!
       
  2077 
       
  2078 version
       
  2079     ^ '$Header$'
       
  2080 ! !