so far so good
authorca
Fri, 28 Mar 1997 15:57:20 +0100
changeset 89 35c5711729c2
parent 88 d6dccf1ad344
child 90 c18809a425d0
so far so good
UIObjectView.st
UIPainterView.st
--- a/UIObjectView.st	Tue Mar 18 10:58:13 1997 +0100
+++ b/UIObjectView.st	Fri Mar 28 15:57:20 1997 +0100
@@ -1,6 +1,6 @@
 ObjectView subclass:#UIObjectView
-	instanceVariableNames:'inputView testMode undoHistory copiedExtent actionData
-		createClass clipChildren selectionHiddenLevel
+	instanceVariableNames:'inputView testMode undoHistory copiedExtent copiedLayout
+		actionData createClass clipChildren selectionHiddenLevel
 		setOfSuperViewsSizeChanged'
 	classVariableNames:''
 	poolDictionaries:''
@@ -464,10 +464,11 @@
 createWidgetWithClass:aClass
     "prepare to create new widgets
     "
-    createClass := aClass.
-    pressAction := [:pressPoint | self startCreate:pressPoint].
-    self cursor:Cursor origin.
-
+    aClass notNil ifTrue:[
+        createClass := aClass.
+        pressAction := [:aPoint| self startCreate:aPoint].
+        self cursor:Cursor origin.
+    ]
 
 !
 
@@ -501,14 +502,13 @@
 endCreate
     "end a widget create drag
     "
-    |layout x y object|
+    |object specClass|
 
     object := actionData object.
     self invertOutlineOf:object.
     inputView raise.
 
-    object superView specClass basicNew setupInitialLayoutFor:object.
-
+    self setupInitialLayoutFor:object.
     self changed:#tree.
     self select:object.
     actionData := nil.
@@ -521,24 +521,39 @@
     self subclassResponsibility
 !
 
+setupInitialLayoutFor:anObject
+    "setup initial layout for an object; !!!! some kludge !!!!
+    "
+    |spec topSpec|
+
+    topSpec := anObject superView specClass basicNew.
+
+    topSpec class isLayoutContainer ifFalse:[
+
+"/ ... KLUDGE ....
+
+        spec := anObject specClass.
+
+        (    spec == ViewSpec
+         or:[spec == SubCanvasSpec
+         or:[spec == TextEditorSpec
+         or:[spec == SequenceViewSpec]]]
+        ) ifTrue:[
+            anObject geometryLayout:(anObject bounds asLayout).
+          ^ self
+        ]
+    ].
+    topSpec setupInitialLayoutFor:anObject.
+
+!
+
 startCreate:aPoint
     "start a widget create
     "
     |widget object start frame delta|
 
-    self selection notNil ifTrue:[
-        self numberOfSelections > 1 ifTrue:[
-            self warn:'to much elements selected'.
-          ^ self setDefaultActions.
-        ].
-        self unselect
-    ].
-
-    (    (widget := self findObjectAt:aPoint) notNil
-     and:[widget specClass supportsSubComponents]
-    ) ifFalse:[
-        widget := self
-    ].
+    self unselect.
+    widget := self findContainerViewAt:aPoint.
 
     motionAction  := [:movePoint| self doDragCreate:movePoint].
     releaseAction := [ self endCreate].
@@ -559,8 +574,6 @@
     self actionCreate:object frame:frame delta:delta.
     object extent:(actionData minExtent).
     object realize.
-
-    self actionCreate:object frame:frame delta:delta.
     self invertOutlineOf:object.
 ! !
 
@@ -1062,6 +1075,14 @@
 
 !UIObjectView methodsFor:'searching'!
 
+findContainerViewAt:aPoint
+    "find container view responds to aPoint.
+    "
+    ^ self subclassResponsibility
+
+
+!
+
 findObjectAt:aPoint
     "find the origin/corner of the currentWidget
     "
@@ -1428,6 +1449,23 @@
 
 !
 
+copyLayout
+    "copy the layout from the selected object
+    "
+    |object|
+
+    object := self singleSelection.
+
+    object notNil ifTrue:[
+        copiedLayout := object geometryLayout copy
+    ] ifFalse:[
+        self warn:'exactly one element must be selected'.
+    ]
+
+
+
+!
+
 pasteExtent
     "paste the copied extent to all objects in the selection
     "
@@ -1449,6 +1487,16 @@
 
 !
 
+pasteLayout
+    "paste layout to all objects in the selection
+    "
+    copiedLayout notNil ifTrue:[
+        self transition:#pasteLayout dimensionDo:[:v|
+            v geometryLayout:(copiedLayout copy)
+        ]    
+    ]    
+!
+
 pasteWidth
     "paste the copied extent width to all objects in the selection
     "
--- a/UIPainterView.st	Tue Mar 18 10:58:13 1997 +0100
+++ b/UIPainterView.st	Fri Mar 28 15:57:20 1997 +0100
@@ -183,13 +183,23 @@
 pasteBuffer
     "add the objects in the paste-buffer to the object view
     "
+    self pasteSpecifications:(self getSelection) keepLayout:false
+
+!
+
+pasteSpecifications:aSpecificationOrList keepLayout:keepLayout
+    "add the specs to the object view
+    "
     |paste frame pasteOrigin pasteOffset builder|
 
-    paste := self getSelection.
-
-    (self canPaste:paste) ifFalse:[ ^ self].
-    (paste isCollection)  ifFalse:[ paste := Array with:paste].
-
+    (self canPaste:aSpecificationOrList) ifFalse:[
+        ^ self
+    ].
+    aSpecificationOrList isCollection ifTrue:[
+        paste := aSpecificationOrList
+    ] ifFalse:[
+        paste := Array with:aSpecificationOrList
+    ].
     frame := self singleSelection.
 
     (self canPasteInto:frame) ifFalse:[
@@ -197,26 +207,30 @@
     ].
     self unselect.
 
-    selection   := OrderedCollection new.
-    pasteOffset := 0@0.
-    pasteOrigin := self sensor mousePoint.
-    pasteOrigin := device translatePoint:pasteOrigin from:device rootView id to:frame id.
-    builder     := UIBuilder new.
+    selection := OrderedCollection new.
+    builder   := UIBuilder new.
+
+    keepLayout ifFalse:[
+        pasteOffset := 0@0.
+        pasteOrigin := self sensor mousePoint.
+        pasteOrigin := device translatePoint:pasteOrigin from:device rootView id to:frame id.
+    ].
 
     paste do:[:aSpec|
         |view|
 
         view := self addSpec:aSpec builder:builder in:frame.
 
-        (frame bounds containsPoint:pasteOrigin) ifFalse:[
-            self moveObject:view to:pasteOffset.
-        ] ifTrue:[
-            self moveObject:view to:pasteOrigin + pasteOffset.
+        keepLayout ifFalse:[
+            (frame bounds containsPoint:pasteOrigin) ifFalse:[
+                self moveObject:view to:pasteOffset.
+            ] ifTrue:[
+                self moveObject:view to:pasteOrigin + pasteOffset.
+            ].
+            pasteOffset := pasteOffset + 4
         ].
-
         view realize.
         selection add:view.
-        pasteOffset := pasteOffset + 4.
     ].
 
     self transaction:#paste selectionDo:[:v|
@@ -231,19 +245,35 @@
     self elementChangedSize:frame.
     self changed:#tree
 
+!
+
+pasteWithLayout
+    "add the objects in the paste-buffer to the object view; don't change the
+     layout
+    "
+    self pasteSpecifications:(self getSelection) keepLayout:true
+
 ! !
 
 !UIPainterView methodsFor:'drag & drop'!
 
 canDrop:anObjectOrCollection
-    Transcript showCR:'canDrop'.
-    ^ true
+    |spec|
 
-
+    testMode ifFalse:[
+        anObjectOrCollection size == 1 ifTrue:[
+            spec := (anObjectOrCollection at:1) theObject.
+          ^ (spec isKindOf:UISpecification)
+        ]
+    ].
+    ^ false
 !
 
 drop:anObjectOrCollection at:aPoint
-    Transcript showCR:'drop:anObjectOrCollection at:aPoint'.
+    |spec|
+
+    spec := (anObjectOrCollection at:1) theObject.
+    self pasteSpecifications:spec keepLayout:false.
 
 
 ! !
@@ -283,6 +313,7 @@
         self warn:'set the class first'.
         ^ code
     ].
+    cls := Smalltalk classNamed:className.
 
     viewProperties do:[:aProp |
         |modelSelector menuSelector protoSpec thisCode|
@@ -311,9 +342,7 @@
     ].
     ^ code
 
-! !
-
-!UIPainterView ignoredMethodsFor:'generating output'!
+!
 
 generateClassDefinition
     |defCode|
@@ -330,9 +359,7 @@
 
 
 
-! !
-
-!UIPainterView methodsFor:'generating output'!
+!
 
 generateCode
     "generate code for the windowSpec method"
@@ -353,9 +380,7 @@
     ^ code withCRs
 
     "Modified: 5.9.1995 / 20:57:53 / claus"
-! !
-
-!UIPainterView ignoredMethodsFor:'generating output'!
+!
 
 generateInitCodeForGroup:aGroup
     |code c name p objects outlets moreCode sym typ val|
@@ -513,9 +538,7 @@
 
 generateOutlets
     ^ self
-! !
-
-!UIPainterView methodsFor:'generating output'!
+!
 
 generateWindowSpecMethodSource
     |t s spec specArray str code|
@@ -564,15 +587,11 @@
     ^ code withCRs
 
     "Modified: 5.9.1995 / 21:01:35 / claus"
-! !
-
-!UIPainterView ignoredMethodsFor:'generating output'!
+!
 
 nameOfClass
     ^ 'NewView'
-! !
-
-!UIPainterView methodsFor:'generating output'!
+!
 
 outletValueOf:aSymbol for:aView
 "/    |c name p outlets moreCode sym typ val|
@@ -750,11 +769,8 @@
         undoIdx := 2.
 
         menu := PopUpMenu labels:( resources array:#('paste' 'undo') )
-                       selectors:#( #pasteBuffer #undoLast )
-                    accelerators:#( #Paste       nil )
-                        receiver:self.
-
-        canPaste ifFalse:[menu disable:#pasteBuffer].
+                       selectors:#( #paste #undoLast )
+                        receiver:self
     ] ifFalse:[    
         undoIdx := 4.
 
@@ -771,7 +787,7 @@
                                   )
                        selectors:#(   #copySelection
                                       #deleteSelection
-                                      #pasteBuffer
+                                      #paste
                                       #undoLast
                                       nil
                                       #arrange
@@ -780,7 +796,7 @@
                                   )
                        accelerators:#(#Copy
                                       #Cut
-                                      #Paste
+                                      nil
                                       nil
                                       nil
                                       nil
@@ -789,14 +805,15 @@
                                   )
                          receiver:self.
 
-        (canPaste and:[self canPasteInto:selection]) ifFalse:[
-            menu disable:#pasteBuffer
-        ].
+        canPaste := (canPaste and:[self canPasteInto:selection]).
         menu subMenuAt:#arrange   put:(self subMenuArrange).
         menu subMenuAt:#dimension put:(self subMenuDimension).
         menu subMenuAt:#align     put:(self subMenuAlign).
     ].
 
+    menu subMenuAt:#paste put:(self subMenuPaste).
+    canPaste ifFalse:[menu disable:#paste].
+
     undoText notNil ifTrue:[
         menu labelAt:undoIdx put:((menu labels at:undoIdx), ':  ', undoText)
     ] ifFalse:[
@@ -903,6 +920,9 @@
                                     'paste extent'
                                     'paste width'
                                     'paste height'
+                                    '-'
+                                    'copy  layout'
+                                    'paste layout'
                                  )
                               )
                    selectors:#(
@@ -915,6 +935,9 @@
                                     pasteExtent
                                     pasteWidth
                                     pasteHeight
+                                    nil
+                                    copyLayout
+                                    pasteLayout
                               )
                      receiver:self.
   ^ menu
@@ -951,6 +974,20 @@
                               )
                      receiver:self.
   ^ menu
+!
+
+subMenuPaste
+    "returns submenu Paste
+    "
+    |menu|
+
+    menu := PopUpMenu labels:( resources array:#('paste' 'keep layout') )
+                   selectors:#( #pasteBuffer #pasteWithLayout )
+                accelerators:#( #Paste       nil )
+                    receiver:self.
+
+  ^ menu    
+
 ! !
 
 !UIPainterView methodsFor:'misc'!
@@ -1015,6 +1052,24 @@
 
 !UIPainterView methodsFor:'searching'!
 
+findContainerViewAt:aPoint
+    "find container view responds to aPoint.
+    "
+    |view|
+
+    (view := self findObjectAt:aPoint) isNil ifTrue:[
+        ^ self
+    ].
+
+    [(view specClass supportsSubComponents or:[(view := view superView) == self])
+    ] whileFalse:[
+        [(self propertyOfView:view) isNil] whileTrue:[
+            (view := view superView) == self ifTrue:[^ self]
+        ].
+    ].
+    ^ view
+!
+
 findObjectAt:aPoint
     "find the origin/corner of the currentWidget
     "