[Pkg] The Trunk: Morphic-cmm.679.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Sep 10 02:08:56 UTC 2013


Chris Muller uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-cmm.679.mcz

==================== Summary ====================

Name: Morphic-cmm.679
Author: cmm
Time: 9 September 2013, 9:07:28.315 pm
UUID: 0e960d78-53c8-4ca3-9f3a-59b4ff49483d
Ancestors: Morphic-nice.679

- Introducing Smart-Splitters.  
- Yellow-click a splitter bar to make it to move to an ideal position.  
- Turn on "Smart Vertical Splitters" and vertical bars between lists will automatically reposition themselves to balance the number of characters occluded on either side of the bar, if necessary.
- Turn on "Smart Horizontal Splitters" and horizontal splitter bars will automatically reposition themselves to increase the quantity of exposed information, if necessary and possible.
- With the preference(s) on, if a particular splitter is manually positioned, it will remain still at the dragged location.  To reactivate automatic-positioning, yellow-click it.
- Improve on the prior increase in constrast with #flash by negating the color _after_ increasing its saturation, not before.

=============== Diff against Morphic-nice.679 ===============

Item was added:
+ ----- Method: Morph>>canBeEncroached (in category 'private') -----
+ canBeEncroached
+ 	"Support for the #smartHorizontalSplitters preference."
+ 	^ true!

Item was changed:
  ----- Method: Morph>>flash (in category 'macpal') -----
  flash
  	| originalColor |
  	originalColor := self color.
  	[ self color:
  		(originalColor
  			ifNil: [ Color black ]
+ 			ifNotNil: [( (originalColor alpha: 1) adjustSaturation: 0.8 brightness: 0) negated ]) ]
- 			ifNotNil: [ (originalColor alpha: 1) negated adjustSaturation: 0.8 brightness: 0 ]) ]
  		ensure:
  			[ self world ifNotNil: [ : w | w displayWorldSafely ].
  			self color: originalColor ]!

Item was added:
+ ----- Method: Object>>isPluggableListMorph (in category '*morphic') -----
+ isPluggableListMorph
+ 	^ false!

Item was added:
+ ----- Method: PluggableListMorph>>bottomVisibleRowIndex (in category 'accessing') -----
+ bottomVisibleRowIndex
+ 	^ self rowAtLocation: self bottomLeft+(3 at 3 negated)!

Item was added:
+ ----- Method: PluggableListMorph>>canBeEncroached (in category 'testing') -----
+ canBeEncroached
+ 	"Answer whether my bottom edge can be encroached by horizontal smart-splitter.  If my list is larger than my outermost containing window, go ahead and report true since moving a splitter will never allow my entire list to be displayed.  In that case go ahead and be encroachable to allow lower truncated text-panes to be exposed, but leave a reasonable height (70) to ensure at least few items are displayed."
+ 	^ self height > 24 and:
+ 		[ | outermostContainer |
+ 		outermostContainer := self outermostMorphThat:
+ 			[ : e | e owner = World ].
+ 		listMorph height + 8 < self height or:
+ 			[ outermostContainer notNil and: [ listMorph height > (outermostContainer height / 1.2) and: [ self height > 70 ] ] ] ]!

Item was added:
+ ----- Method: PluggableListMorph>>charactersOccluded (in category 'accessing') -----
+ charactersOccluded
+ 	"Answer the number of characters occluded in my #visibleList by my right edge."
+ 	^ self visibleList
+ 		inject: 0
+ 		into:
+ 			[ : sum : each | | eachString totalWidth indexOfLastVisible |
+ 			totalWidth := 0.
+ 			eachString := each asString "withBlanksTrimmed".
+ 			indexOfLastVisible := ((1 to: eachString size)
+ 				detect:
+ 					[ : index | (totalWidth := totalWidth + (self font widthOf: (eachString at: index))) >
+ 						(self width -
+ 							(scrollBar
+ 								ifNil: [ 0 ]
+ 								ifNotNil: [ scrollBar width ])) ]
+ 				ifNone: [ eachString size + 1 ]) - 1.
+ 			sum + (eachString size - indexOfLastVisible) ]!

Item was added:
+ ----- Method: PluggableListMorph>>isPluggableListMorph (in category 'drawing') -----
+ isPluggableListMorph
+ 	^ true!

Item was added:
+ ----- Method: PluggableListMorph>>topVisibleRowIndex (in category 'accessing') -----
+ topVisibleRowIndex
+ 	^ self rowAtLocation: self topLeft+(3 at 3)!

Item was changed:
  ----- Method: PluggableListMorph>>verifyContents (in category 'updating') -----
  verifyContents
  	"Verify the contents of the receiver, reconstituting if necessary.  Called whenever window is reactivated, to react to possible structural changes.  Also called periodically in morphic if the smartUpdating preference is true"
  	| newList existingSelection anIndex oldList |
  	oldList := list ifNil: [ #() ].
  	newList := self getList.
  	oldList = newList ifTrue: [ ^ self ].
+ 	existingSelection :=  oldList at: self selectionIndex ifAbsent: [ nil ].
- 	existingSelection := self selectionIndex > 0 ifTrue: [ oldList at: self selectionIndex ] ifFalse: [ nil ].
  	self updateList.
  	(existingSelection notNil and: [(anIndex := self getFullList indexOf: existingSelection asStringOrText ifAbsent: [nil]) notNil])
  		ifTrue:
  			[model noteSelectionIndex: anIndex for: getListSelector.
  			self selectionIndex: anIndex]
  		ifFalse:
  			[self changeModelSelection: 0]!

Item was added:
+ ----- Method: PluggableListMorph>>visibleList (in category 'accessing') -----
+ visibleList
+ 	"Fix this to return just the items that are in the list."
+ 	^ list isEmptyOrNil
+ 		ifTrue: [ Array empty ]
+ 		ifFalse:
+ 			[ list
+ 				copyFrom: self topVisibleRowIndex
+ 				to: (self bottomVisibleRowIndex min: list size) ]!

Item was added:
+ ----- Method: PluggablePanelMorph>>canBeEncroached (in category 'private') -----
+ canBeEncroached
+ 	^ submorphs allSatisfy:
+ 		[ : each | each canBeEncroached ]!

Item was added:
+ ----- Method: PluggablePanelMorph>>children (in category 'accessing') -----
+ children
+ 	^ model perform: getChildrenSelector!

Item was changed:
  ----- Method: PluggablePanelMorph>>update: (in category 'update') -----
+ update: selectorSymbolOrNil 
+ 	selectorSymbolOrNil ifNil: [ ^ self ].
+ 	selectorSymbolOrNil = getChildrenSelector ifTrue:
+ 		[ self
+ 			 removeAllMorphs ;
+ 			 addAllMorphs: self children ;
+ 			 submorphsDo:
+ 				[ : m | m
+ 					 hResizing: #spaceFill ;
+ 					 vResizing: #spaceFill ] ]!
- update: what
- 	what == nil ifTrue:[^self].
- 	what == getChildrenSelector ifTrue:[
- 		self removeAllMorphs.
- 		self addAllMorphs: (model perform: getChildrenSelector).
- 		self submorphsDo:[:m| m hResizing: #spaceFill; vResizing: #spaceFill].
- 	].!

Item was added:
+ ----- Method: PluggableTextMorph>>canBeEncroached (in category 'testing') -----
+ canBeEncroached
+ 	"Fixed-height always report true, since they cannot be encroached."
+ 	self layoutFrame ifNotNil: [ : frame | frame topFraction = frame bottomFraction ifTrue: [ ^ true ] ].
+ 	^ (textMorph height+10) < self height!

Item was changed:
  AbstractResizerMorph subclass: #ProportionalSplitterMorph
  	instanceVariableNames: 'leftOrTop rightOrBottom splitsTopAndBottom oldColor traceMorph handle'
+ 	classVariableNames: 'SmartHorizontalSplitters SmartVerticalSplitters'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Windows'!
  
  !ProportionalSplitterMorph commentStamp: 'jmv 1/29/2006 17:16' prior: 0!
  I am the morph the user grabs to adjust pane splitters.!

Item was added:
+ ----- Method: ProportionalSplitterMorph class>>preferenceChanged: (in category 'private') -----
+ preferenceChanged: aBoolean
+ 	"Take immediate effect for all in a  World."
+ 	self allInstances do:
+ 		[ : each | each isInWorld ifTrue:
+ 			[ aBoolean
+ 				ifTrue: [ each startStepping ]
+ 				ifFalse: [ each stopStepping ] ] ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph class>>smartHorizontalSplitters (in category 'preferences') -----
+ smartHorizontalSplitters
+ 	<preference: 'Smart Horizontal Splitters'
+ 		category: 'Morphic'
+ 		description: 'When true, horizontal splitter bars will automatically reposition themselves to increase the quantity of exposed information, if possible..'
+ 		type: #Boolean>
+ 	^ SmartHorizontalSplitters ifNil: [ false ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph class>>smartHorizontalSplitters: (in category 'preferences') -----
+ smartHorizontalSplitters: aBoolean 
+ 	SmartHorizontalSplitters := aBoolean.
+ 	self preferenceChanged: aBoolean!

Item was added:
+ ----- Method: ProportionalSplitterMorph class>>smartVerticalSplitters (in category 'preferences') -----
+ smartVerticalSplitters
+ 	<preference: 'Smart Vertical Splitters'
+ 		category: 'Morphic'
+ 		description: 'When true, vertical bars between lists will automatically reposition themselves to balance the number of characters occluded on either side of the bar.'
+ 		type: #Boolean>
+ 	^ SmartVerticalSplitters ifNil: [ false ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph class>>smartVerticalSplitters: (in category 'preferences') -----
+ smartVerticalSplitters: aBoolean 
+ 	SmartVerticalSplitters := aBoolean.
+ 	self preferenceChanged: aBoolean!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>canEncroachWhiteSpaceOf: (in category 'layout') -----
+ canEncroachWhiteSpaceOf: morphs 
+ 	^ morphs allSatisfy: [ : each | each canBeEncroached ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>charactersOccludedIn: (in category 'layout') -----
+ charactersOccludedIn: aCollection
+ 	^ aCollection
+ 		inject: 0
+ 		into:
+ 			[ : max : each | max max:
+ 				(each isPluggableListMorph
+ 					ifTrue: [ each charactersOccluded ]
+ 					ifFalse: [ 0 ]) ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>leftRightImbalance (in category 'layout') -----
+ leftRightImbalance
+ 	"First check if I find myself out of range due to user having reduced size of parent."
+ 	^ self left < self leftBoundary "too far left"
+ 		ifTrue: [ self leftBoundary-self left ]
+ 		ifFalse:
+ 			[ self right > self rightBoundary "too far right"
+ 				ifTrue: [ self right-self rightBoundary ]
+ 				ifFalse: [ self occlusionDifference ] ]!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>mouseDown: (in category 'events') -----
  mouseDown: anEvent 
+ 	"If the user manually drags me, don't override him with auto positioning."
+ 	anEvent redButtonChanged
+ 		ifTrue: [ self stopStepping ]
+ 		ifFalse:
+ 			[ anEvent shiftPressed
+ 				ifTrue: [ self startStepping ]
+ 				ifFalse:
+ 					[ {self} , self siblingSplitters do:
+ 						[ : each | each startStepping ] ] ].
+ 	(self class showSplitterHandles not and: [ self bounds containsPoint: anEvent cursorPoint ]) ifTrue:
+ 		[ oldColor := self color.
+ 		self color: Color black ].
+ 	^ super mouseDown: anEvent!
- 	(self class showSplitterHandles not
- 			and: [self bounds containsPoint: anEvent cursorPoint])
- 		ifTrue: [oldColor := self color.
- 			self color: Color black].
- 	^ super mouseDown: anEvent !

Item was added:
+ ----- Method: ProportionalSplitterMorph>>occlusionDifference (in category 'events') -----
+ occlusionDifference
+ 	^ (self charactersOccludedIn: leftOrTop) - (self charactersOccludedIn: rightOrBottom)!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>repositionBy: (in category 'layout') -----
+ repositionBy: delta
+ 	| selfTop selfBottom selfLeft selfRight |
+ 	leftOrTop do:
+ 		[ : each | | firstRight firstBottom |
+ 		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 secondTop |
+ 		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 ;
+ 		 bottomOffset: selfBottom + delta y ;
+ 		 leftOffset: selfLeft + delta x ;
+ 		 rightOffset: selfRight + delta x.
+ 	self owner layoutChanged!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>step (in category 'events') -----
+ step
+ 	| correction |
+ 	splitsTopAndBottom
+ 		ifTrue:
+ 			[ (correction := self topBottomCorrection) isZero
+ 				ifTrue: [ self class smartHorizontalSplitters ifFalse: [ self stopStepping ] ]
+ 				ifFalse: [ self repositionBy: 0 @ correction ] ]
+ 		ifFalse:
+ 			[ correction := self leftRightImbalance.
+ 			correction abs > 1
+ 				ifTrue:
+ 					[ self repositionBy:
+ 						(correction abs > 4
+ 							ifTrue: [ correction sign * 2 @ 0 ]
+ 							ifFalse: [ correction sign @ 0 ]) ]
+ 				ifFalse:
+ 					[ self class smartVerticalSplitters ifFalse: [ self stopStepping ] ] ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>stepTime (in category 'events') -----
+ stepTime
+ 	| pause |
+ 	"When a splitter finds itself in the right place, let it rest for about 3 seconds to avoid performance impacts of constant, rapid stepping."
+ 	pause := (2900 to: 3100) atRandom "to discourage any patternistic emergence".
+ 	^ splitsTopAndBottom
+ 		ifTrue:
+ 			[ self topBottomCorrection isZero
+ 				ifTrue: [ pause ]
+ 				ifFalse: [ 0 ] ]
+ 		ifFalse:
+ 			[ self leftRightImbalance abs > 1 ">1 rather than 0 to discourage one-off twitching"
+ 				ifTrue: [ 0 ]
+ 				ifFalse: [ pause ] ]!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>topBottomCorrection (in category 'layout') -----
+ topBottomCorrection
+ 	"First check if I find myself out of range due to user having reduced size of parent."
+ 	^ self bottom < self topBoundary "too high"
+ 		ifTrue: [ 2 ]
+ 		ifFalse:
+ 			[ self top > self bottomBoundary "too low"
+ 				ifTrue: [ -2 ]
+ 				ifFalse:
+ 					[ | wsAbove wsBelow |
+ 					wsAbove := self canEncroachWhiteSpaceOf: leftOrTop.
+ 					wsBelow := self canEncroachWhiteSpaceOf: rightOrBottom.
+ 					wsAbove
+ 						ifTrue:
+ 							[ (wsBelow not and: [ self top > (self topBoundary + 25) ])
+ 								ifTrue: [ -2 ]
+ 								ifFalse: [ 0 ] ]
+ 						ifFalse:
+ 							[ wsBelow
+ 								ifTrue:
+ 									[ self bottom < (self bottomBoundary - 25)
+ 										ifTrue: [ 2 ]
+ 										ifFalse: [ 0 ] ]
+ 								ifFalse: [ 0 ] ] ] ]!

Item was changed:
  ----- Method: ProportionalSplitterMorph>>updateFromEvent: (in category 'events') -----
  updateFromEvent: anEvent 
+ 	| delta |
- 	| delta selfTop selfBottom selfLeft selfRight |
  	delta := splitsTopAndBottom
+ 		ifTrue: [ 0 @ ((self normalizedY: anEvent cursorPoint y) - lastMouse y) ]
+ 		ifFalse: [ (self normalizedX: anEvent cursorPoint x) - lastMouse x @ 0 ].
+ 	lastMouse := splitsTopAndBottom
+ 		ifTrue: [ lastMouse x @ (self normalizedY: anEvent cursorPoint y) ]
+ 		ifFalse: [ (self normalizedX: anEvent cursorPoint x) @ lastMouse y ].
+ 	self repositionBy: delta!
- 				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 firstBottom | 
- 					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 secondTop | 
- 					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!

Item was added:
+ ----- Method: ProportionalSplitterMorph>>wantsSteps (in category 'events') -----
+ wantsSteps
+ 	^ splitsTopAndBottom
+ 		ifTrue: [ self class smartHorizontalSplitters ]
+ 		ifFalse: [ self class smartVerticalSplitters ]!

Item was added:
+ ----- Method: ScrollPane>>canBeEncroached (in category 'testing') -----
+ canBeEncroached
+ 	"For support of the smartHorizontalSplitters preference."
+ 	^ scrollBar isInWorld not!



More information about the Packages mailing list