Bounding up morphs

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Thu Jan 30 18:12:10 UTC 2003


Eric:

You can use one modified SelectionMorph , such what you can add code fit to
your use.
I attach my solution for a project what I doing.
Your morph don't more had to be in a World (mine has be over a my choosen
morph)
And don not loose former positions

Edgar

-------------- next part --------------
'From Squeak3.4gamma of ''7 January 2003'' [latest update: #5168] on 30 January 2003 at 3:05:50 pm'!
BorderedMorph subclass: #TrackSelectionMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'RailRoad'!

!TrackSelectionMorph methodsFor: 'initialization' stamp: 'EDC 10/5/2002 07:01'!
initialize
	super initialize.
	color _ Color transparent.
	borderWidth _ 2.
	borderColor _ Color red.! !


!TrackSelectionMorph methodsFor: 'submorphs-add/remove' stamp: 'EDC 10/5/2002 08:15'!
addMorph: aMorph 
	| |
	super addMorph: aMorph.
	
	self newExtent! !

!TrackSelectionMorph methodsFor: 'submorphs-add/remove' stamp: 'EDC 10/30/2002 08:16'!
newExtent
	| minLeft minTop minRight minBottom oldPositions |
	minLeft _ (submorphs
				collect: [:itm | itm left]) min.
	minTop _ (submorphs
				collect: [:itm | itm top]) min.
	minRight _ (submorphs
				collect: [:itm | itm right]) max.
	minBottom _ (submorphs
				collect: [:itm | itm bottom]) max.
oldPositions _ (submorphs
				collect: [:itm | itm position]) .
	self
		bounds: (Rectangle origin: minLeft @ minTop corner: minRight @ minBottom).
	submorphs with: oldPositions do: [:each :oldP | each position: oldP]! !


!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 8/31/2000 22:29'!
addHandlesTo: aHaloMorph box: box
	| onlyThese |
	aHaloMorph haloBox: box.
	onlyThese _ #(addDismissHandle: addMenuHandle: addGrabHandle: addDragHandle: addDupHandle: addHelpHandle: addGrowHandle: addFontSizeHandle: addFontStyleHandle: addFontEmphHandle: addRecolorHandle:).
	Preferences haloSpecifications do:
		[:aSpec | (onlyThese includes: aSpec addHandleSelector) ifTrue:
				[aHaloMorph perform: aSpec addHandleSelector with: aSpec]].
	aHaloMorph innerTarget addOptionalHandlesTo: aHaloMorph box: box! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 8/31/2000 22:59'!
addOptionalHandlesTo: aHalo box: box
	aHalo addHandleAt: box leftCenter color: Color blue icon: nil
		on: #mouseUp send: #addOrRemoveItems: to: self.! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/29/2002 10:47'!
addOrRemoveItems: handOrEvent 
	"Make a new selection extending the current one."
	| oldOwner hand |
	hand _ (handOrEvent isKindOf: HandMorph)
				ifTrue: [handOrEvent]
				ifFalse: [handOrEvent hand].
self halt.
	hand
		addMorphBack: ((self class
				newBounds: (hand lastEvent cursorPoint extent: 16 @ 16))
				setOtherSelection: self).
	oldOwner _ owner.
	self world abandonAllHalos.
	"Will delete me"
	oldOwner addMorph: self! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:15'!
alignBottomEdges
	"Make the bottom coordinate of all my elements be the same"
	| maxBottom |
	maxBottom _ (submorphs
				collect: [:itm | itm bottom]) max.
	submorphs
		do: [:itm | itm bottom: maxBottom].
self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:15'!
alignCentersHorizontally
	"Make every morph in the selection have the same vertical center as the 
	topmost item."
	| minLeft leftMost |
	submorphs size > 1
		ifFalse: [^ self].
	minLeft _ (submorphs
				collect: [:itm | itm left]) min.
	leftMost _ submorphs
				detect: [:m | m left = minLeft].
	submorphs
		do: [:itm | itm center: itm center x @ leftMost center y].
	self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:15'!
alignCentersVertically
	"Make every morph in the selection have the same horizontal center as 
	the topmost item."
	| minTop topMost |
	submorphs size > 1
		ifFalse: [^ self].
	minTop _ (submorphs
				collect: [:itm | itm top]) min.
	topMost _ submorphs
				detect: [:m | m top = minTop].
	submorphs
		do: [:itm | itm center: topMost center x @ itm center y].
	self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:16'!
alignLeftEdges
	"Make the left coordinate of all my elements be the same"
	| minLeft |
	minLeft _ (submorphs
				collect: [:itm | itm left]) min.
	submorphs
		do: [:itm | itm left: minLeft].
	self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:16'!
alignRightEdges
	"Make the right coordinate of all my elements be the same"
	| maxRight |
	maxRight _ (submorphs
				collect: [:itm | itm right]) max.
	submorphs
		do: [:itm | itm right: maxRight].
	self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'EDC 10/5/2002 08:16'!
alignTopEdges
	"Make the top coordinate of all my elements be the same"
	| minTop |
	minTop _ (submorphs
				collect: [:itm | itm top]) min.
	submorphs
		do: [:itm | itm top: minTop].
	self newExtent! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 8/31/2000 22:59'!
balloonHelpTextForHandle: aHandle
	aHandle eventHandler firstMouseSelector == #addOrRemoveItems:
		ifTrue: [^'Add items to, or remove them from, this selection.'].
	^ super balloonHelpTextForHandle: aHandle! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 9/19/2000 18:25'!
borderColor: aColor

	| bordered |
	bordered _ submorphs select: [:m | m isKindOf: BorderedMorph].
	undoProperties ifNil: [undoProperties _ bordered collect: [:m | m borderColor]].
	bordered do: [:m | m borderColor: aColor]! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 9/19/2000 18:25'!
borderWidth: aWidth

	| bordered |
	bordered _ submorphs select: [:m | m isKindOf: BorderedMorph].
	undoProperties ifNil: [undoProperties _ bordered collect: [:m | m borderWidth]].
	bordered do: [:m | m borderWidth: aWidth]! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 8/23/2000 17:06'!
dismissViaHalo

	super dismissViaHalo.
	submorphs do: [:m | m dismissViaHalo]! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'nk 3/12/2001 17:08'!
doDup: evt fromHalo: halo handle: dupHandle.

	submorphs _ self duplicateMorphCollection: submorphs.
	submorphs do: [:m | self owner addMorph: m].
	dupDelta == nil
		ifTrue: ["First duplicate operation -- note starting location"
				dupLoc _ self position.
				evt hand grabMorph: self.
				halo removeAllHandlesBut: dupHandle]
		ifFalse: ["Subsequent duplicate does not grab, but only moves me and my morphs"
				dupLoc _ nil.
				self position: self position + dupDelta]
! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 9/19/2000 21:53'!
fillStyle: aColor
	undoProperties ifNil: [undoProperties _ submorphs collect: [:m | m fillStyle]].
	submorphs do: [:m | m fillStyle: aColor]! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'di 8/31/2000 20:50'!
maybeAddCollapseItemTo: aMenu
	"... don't "! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'sw 3/6/2002 00:04'!
organizeIntoColumn
	"Place my objects in a column-enforcing container"

	((AlignmentMorph inAColumn: submorphs) setNameTo: 'Column'; color: Color orange muchLighter; enableDragNDrop: true; yourself) openInHand
! !

!TrackSelectionMorph methodsFor: 'layout-properties' stamp: 'sw 3/6/2002 00:04'!
organizeIntoRow
	"Place my objects in a row-enforcing container"

	((AlignmentMorph inARow: submorphs) setNameTo: 'Row'; color: Color orange muchLighter; enableDragNDrop: true; yourself) openInHand
! !


!TrackSelectionMorph methodsFor: 'event handling' stamp: 'EDC 10/5/2002 07:54'!
handlesMouseDown: evt 
	"Prevent stray clicks from picking up the whole game in MVC."
	^ Smalltalk isMorphic not
		or: [evt yellowButtonPressed]! !

!TrackSelectionMorph methodsFor: 'event handling' stamp: 'EDC 10/5/2002 07:54'!
mouseDown: evt 
	| menu |
	evt yellowButtonPressed
		ifFalse: [^ evt hand waitForClicksOrDrag: self event: evt].
	menu _ MenuMorph new defaultTarget: self.
	self addMenuItemsTo: menu hand: evt hand.
	menu popUpEvent: evt in: self world! !


!TrackSelectionMorph methodsFor: 'miscellaneous' stamp: 'EDC 10/8/2002 07:02'!
deSelect
	| acambiar |
	acambiar _ submorphs
				collect: [:each | each].
	self delete.
	acambiar do: [:each | each openInWorld].! !

!TrackSelectionMorph methodsFor: 'miscellaneous' stamp: 'EDC 1/30/2003 07:14'!
hacerRecta
	| x1 x2 t largo c |
	
	c _ submorphs
				asSortedCollection: [:a :b | a cuadrante < b cuadrante].
	t _ TrackMorph straight.
	x1 _ submorphs first vertices first x.
	x2 _ submorphs last vertices first x.
	x1 = x2
		ifTrue: [c first cuadrante caseOf: {
				[1] -> [largo _ c last top - c first bottom].
				[3] -> [largo _ c first top - c last bottom]}
				 otherwise: [Transcript open].
			t changeLength: largo * 4.
			t doChangeLength.
			c first cuadrante caseOf: {
				[1] -> 
					[t right: c first right.
					t top: c first bottom].
				[3] -> 
					[t left: c last left.
					t top: c last bottom]}
				 otherwise: [Transcript open]]
		ifFalse: [largo _ c last right - c first left.
			t changeLength: largo * 4.
			t doChangeLength.
			self halt.
			c first cuadrante caseOf: {
				[1] -> 
					[t rotar: 90.
					t left: c last right.
					t top: c first top].
				[2] -> 
					[t rotar: 90.
					t left: c last right.
					t bottom: c first bottom].
				[3] -> 
					[t left: c last left.
					t top: c first top].
				[4] -> [self halt]}
				 otherwise: [Transcript open]]! !


!TrackSelectionMorph methodsFor: 'menu' stamp: 'sw 3/19/2002 22:55'!
addCustomMenuItems: aMenu hand: aHandMorph
	"Add custom menu items to the menu"

	super addCustomMenuItems: aMenu hand: aHandMorph.
	aMenu addLine.
	aMenu add: 'add or remove items' target: self selector: #addOrRemoveItems: argument: aHandMorph.
	aMenu addList: #(
		-
		('place into a row' organizeIntoRow)
		('place into a column' organizeIntoColumn)
		-
		('align left edges' alignLeftEdges)
		('align top edges' alignTopEdges)
		('align right edges' alignRightEdges)
		('align bottom edges' alignBottomEdges)
		-
		('align centers vertically' alignCentersVertically)
		('align centers horizontally' alignCentersHorizontally))


! !

!TrackSelectionMorph methodsFor: 'menu' stamp: 'EDC 10/8/2002 06:39'!
addMenuItemsTo: aMenu hand: aHandMorph 
	"Add custom menu items to the menu"
	super addCustomMenuItems: aMenu hand: aHandMorph.
	aMenu
		add: 'hacer recta de union '
		target: self
		action: #hacerRecta.
aMenu
		add: 'eliminar seleccion '
		target: self
		action: #deSelect.
	aMenu addLine.
	aMenu
		add: 'add or remove items'
		target: self
		selector: #addOrRemoveItems:
		argument: aHandMorph.
	aMenu addList: #(#- #('place into a row' #organizeIntoRow) #('place into a column' #organizeIntoColumn) #- #('align left edges' #alignLeftEdges) #('align top edges' #alignTopEdges) #('align right edges' #alignRightEdges) #('align bottom edges' #alignBottomEdges) #- #('align centers vertically' #alignCentersVertically) #('align centers horizontally' #alignCentersHorizontally) )! !


More information about the Squeak-dev mailing list