[FIX] Squeak 3.9 / ProportionalSplitter-honor-boundaries

John Pierce john at pierce.name
Wed Mar 22 04:33:43 UTC 2006


Skipped content of type multipart/alternative-------------- next part --------------
'From Squeak3.9alpha of 4 July 2005 [latest update: #7015] on 21 March 2006 at 11:24:21 pm'!
"Change Set:		ProportionalSplitter-honor-boundaries-jrp
Date:			21 March 2006
Author:			John Pierce

Keep splitter from moving outside the natural window boundaries"!


!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:16'!
bottomBoundary

	^ (self splitterBelow ifNil: [self containingWindow panelRect bottom] ifNotNil: [self splitterBelow top]) - 75! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:09'!
leftBoundary

	^ (self splitterLeft ifNil: [self containingWindow panelRect left] ifNotNil: [self splitterLeft right]) + 50! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:11'!
mouseMove: anEvent 
	anEvent hand temporaryCursor
		ifNil: [^ self].
	self class fastSplitterResize
		ifFalse:  [self updateFromEvent: anEvent]
		ifTrue: [traceMorph
				ifNil: [traceMorph _ Morph newBounds: self bounds.
					traceMorph borderColor: Color lightGray.
					traceMorph borderWidth: 1.
					self owner addMorph: traceMorph].
			splitsTopAndBottom
				ifTrue: [traceMorph position: traceMorph position x @ (self normalizedY: anEvent cursorPoint y)]
				ifFalse: [traceMorph position: (self normalizedX: anEvent cursorPoint x) @ traceMorph position y]]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 22:45'!
normalizedX: x

	^ (x max: self leftBoundary) min: self rightBoundary! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:12'!
normalizedY: y

	^ (y max: self topBoundary) min: self bottomBoundary! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:09'!
rightBoundary

	^ (self splitterRight ifNil: [self containingWindow panelRect right] ifNotNil: [self splitterRight left]) - 50! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 20:20'!
siblingSplitters

	^ self owner submorphsSatisfying: [:each | (each isKindOf: self class) and: [self splitsTopAndBottom = each splitsTopAndBottom] and: [each ~= self]]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:01'!
splitterAbove

	| splitters |
	splitters _ ((self siblingSplitters select: [:each | each y > self y]) asSortedCollection: [:a :b | a y < b y]).
	
	^ splitters ifEmpty: nil ifNotEmpty: [splitters first]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:01'!
splitterBelow

	| splitters |
	splitters _ ((self siblingSplitters select: [:each | each y < self y]) asSortedCollection: [:a :b | a y > b y]).
	
	^ splitters ifEmpty: nil ifNotEmpty: [splitters first]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:03'!
splitterLeft

	| splitters |
	splitters _ ((self siblingSplitters select: [:each | each x < self x]) asSortedCollection: [:a :b | a x > b x]).
	
	^ splitters ifEmpty: nil ifNotEmpty: [splitters first]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:03'!
splitterRight

	| splitters |
	splitters _ ((self siblingSplitters select: [:each | each x > self x]) asSortedCollection: [:a :b | a x < b x]).
	
	^ splitters ifEmpty: nil ifNotEmpty: [splitters first]! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:16'!
topBoundary

	^ (self splitterAbove ifNil: [self containingWindow panelRect top] ifNotNil: [self splitterAbove bottom]) + 75! !

!ProportionalSplitterMorph methodsFor: 'as yet unclassified' stamp: 'jrp 3/21/2006 23:19'!
updateFromEvent: anEvent 
	| delta firstRight firstBottom secondLeft secondTop selfTop selfBottom selfLeft selfRight |
	delta _ splitsTopAndBottom
				ifTrue: [0 @ ((self normalizedY: anEvent cursorPoint y) - lastMouse y)]
				ifFalse: [(self normalizedX: anEvent cursorPoint x) - lastMouse x @ 0].
				
	splitsTopAndBottom
		ifTrue: [lastMouse _ lastMouse x @ (self normalizedY: anEvent cursorPoint y)]
		ifFalse: [lastMouse _ (self normalizedX: anEvent cursorPoint x) @ lastMouse y].

	leftOrTop
				do: [:each | 
					firstRight _ each layoutFrame rightOffset
								ifNil: [0].
					firstBottom _ each layoutFrame bottomOffset
								ifNil: [0].
					each layoutFrame rightOffset: firstRight + delta x.
					each layoutFrame bottomOffset: firstBottom + delta y].
			rightOrBottom
				do: [:each | 
					secondLeft _ each layoutFrame leftOffset
								ifNil: [0].
					secondTop _ each layoutFrame topOffset
								ifNil: [0].
					each layoutFrame leftOffset: secondLeft + delta x.
					each layoutFrame topOffset: secondTop + delta y].
	selfTop _ self layoutFrame topOffset
				ifNil: [0].
	selfBottom _ self layoutFrame bottomOffset
				ifNil: [0].
	selfLeft _ self layoutFrame leftOffset
				ifNil: [0].
	selfRight _ self layoutFrame rightOffset
				ifNil: [0].
	self layoutFrame topOffset: selfTop + delta y.
	self layoutFrame bottomOffset: selfBottom + delta y.
	self layoutFrame leftOffset: selfLeft + delta x.
	self layoutFrame rightOffset: selfRight + delta x.
	self owner layoutChanged! !




More information about the Squeak-dev mailing list