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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 4 22:16:31 UTC 2011


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

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

Name: Morphic-cmm.544
Author: cmm
Time: 4 June 2011, 5:14:33.221 pm
UUID: 216f24ec-f9a9-4958-8bf6-3953f739f7ed
Ancestors: Morphic-bf.543

- Fixed SystemProgressMorph to not ignore the users requested position on the screen.
- After opening a SystemWindow, ActiveHand releaseAllFoci so that the window can be immediately closed with hot-key Command+w when it was opened from a standard TextMorph (e.g., the Search bar).  Useful for quickly inspecting an object or checking the hierarchy without being forced into a fine-motor gesture to close the window.
- When browsing a class from a text string, determine the class from trimming all whitespace, not just CR's.
- When browsing references to a variable, only selectWord if there isn't already a selection.  This fixes the ability to browse references to the last instVar of a class-definition.

=============== Diff against Morphic-bf.543 ===============

Item was changed:
  RectangleMorph subclass: #SystemProgressMorph
+ 	instanceVariableNames: 'activeSlots bars labels font lock requestedPosition'
- 	instanceVariableNames: 'activeSlots bars labels font lock'
  	classVariableNames: 'BarHeight BarWidth Inset UniqueInstance'
  	poolDictionaries: ''
  	category: 'Morphic-Widgets'!
  
  !SystemProgressMorph commentStamp: '<historical>' prior: 0!
  An single instance of this morph class is used to display progress while the system is busy, eg. while it receives code updates or does a fileIn. To give the user progress information you don't deal directly with SystemProgressMorph. You keep on using the well established way of progress notification, that has been a long time in the system, is widely used and does not depend on the existence of SystemProgressMorph. For more information on this look at the example in this class or look at the comment of the method displayProgressAt:from:to:during: in class String.
  
  SystemProgressMorph is not meant to be used as a component inside other morphs.
  
  You can switch back to the old style of progress display by disabling the morphicProgressStyle setting in the morphic section of the preferences.!

Item was changed:
  ----- Method: SystemProgressMorph class>>label:min:max: (in category 'instance creation') -----
  label: shortDescription min: minValue max: maxValue
+ "This method is no longer used, but kept for a while longer to ensure no difficulties updating via the trunk."
+ 	^ self 
+ 		position: Display center
+ 		label: shortDescription
+ 		min: minValue
+ 		max: maxValue!
- 	UniqueInstance ifNil: [UniqueInstance := super new].
- 	^UniqueInstance label: (shortDescription contractTo: 100) min: minValue asFloat max: maxValue asFloat!

Item was added:
+ ----- Method: SystemProgressMorph class>>position:label:min:max: (in category 'instance creation') -----
+ position: aPoint label: shortDescription min: minValue max: maxValue 
+ 	UniqueInstance ifNil: [ UniqueInstance := super new ].
+ 	^ UniqueInstance
+ 		position: aPoint
+ 		label: (shortDescription contractTo: 100)
+ 		min: minValue asFloat
+ 		max: maxValue asFloat!

Item was changed:
  ----- Method: SystemProgressMorph>>freeSlot: (in category 'private') -----
  freeSlot: number
  	number > 0 ifFalse: [^self].
  	lock critical: [| label |
  		label := labels at: number.
  		(label isNil or: [label owner isNil]) ifTrue: [^self]. "Has been freed before"
  		label delete.
  		(bars at: number) delete.
  		activeSlots := activeSlots - 1.
  		activeSlots = 0
  			ifTrue: [self delete]
+ 			ifFalse: [self reposition]]!
- 			ifFalse: [self recenter]]!

Item was changed:
  ----- Method: SystemProgressMorph>>label:min:max: (in category 'private') -----
  label: shortDescription min: minValue max: maxValue
  	| slot range barSize lastRefresh |
+ "This method is no longer used, but kept for a while longer to ensure no difficulties updating via the trunk."
  	((range := maxValue - minValue) < 0 or: [(slot := self nextSlotFor: shortDescription) = 0])
  		ifTrue: [^[:barVal| 0 ]].
  	range <= 0 ifTrue: [self removeMorph: (bars at: slot)].
  	self recenter.
  	self openInWorld.
  	barSize := -1. "Enforces a inital draw of the morph"
  	lastRefresh := 0.
  	^[:barVal | | newBarSize |
  		barVal isString ifTrue: [
  			self setLabel: barVal at: slot.
  			self currentWorld displayWorld].
  		(barVal isNumber and: [range >= 1 and: [barVal between: minValue and: maxValue]]) ifTrue: [
  			newBarSize := (barVal - minValue / range * BarWidth) truncated.
  			newBarSize = barSize ifFalse: [
  				barSize := newBarSize.
  				(bars at: slot) barSize: barSize.
  				Time primMillisecondClock - lastRefresh > 25 ifTrue: [
  					self currentWorld displayWorld.
  					lastRefresh := Time primMillisecondClock]]].
  		slot]
  !

Item was added:
+ ----- Method: SystemProgressMorph>>position:label:min:max: (in category 'private') -----
+ position: aPoint label: shortDescription min: minValue max: maxValue
+ 	| slot range barSize lastRefresh |
+ 	requestedPosition := aPoint.
+ 	((range := maxValue - minValue) < 0 or: [(slot := self nextSlotFor: shortDescription) = 0])
+ 		ifTrue: [^[:barVal| 0 ]].
+ 	range <= 0 ifTrue: [self removeMorph: (bars at: slot)].
+ 	self reposition.
+ 	self openInWorld.
+ 	barSize := -1. "Enforces a inital draw of the morph"
+ 	lastRefresh := 0.
+ 	^[:barVal | | newBarSize |
+ 		barVal isString ifTrue: [
+ 			self setLabel: barVal at: slot.
+ 			self currentWorld displayWorld].
+ 		(barVal isNumber and: [range >= 1 and: [barVal between: minValue and: maxValue]]) ifTrue: [
+ 			newBarSize := (barVal - minValue / range * BarWidth) truncated.
+ 			newBarSize = barSize ifFalse: [
+ 				barSize := newBarSize.
+ 				(bars at: slot) barSize: barSize.
+ 				Time primMillisecondClock - lastRefresh > 25 ifTrue: [
+ 					self currentWorld displayWorld.
+ 					lastRefresh := Time primMillisecondClock]]].
+ 		slot]
+ !

Item was changed:
  ----- Method: SystemProgressMorph>>recenter (in category 'private') -----
  recenter
  	| position |
+ "This method is no longer used, but kept for a while longer to ensure no difficulties updating via the trunk."
  	"Put ourself in the center of the display"
  	self align: self fullBounds center with: Display boundingBox center.
  	"Check to see if labels are wider than progress bars. In that case do
  	a centered instead of the default left aligned layout."
  	position :=	self width > (Inset x * 2 + (self borderWidth * 2) + BarWidth)
  					ifTrue: [#topCenter]
  					ifFalse: [#leftCenter].
  	self cellPositioning: position!

Item was added:
+ ----- Method: SystemProgressMorph>>reposition (in category 'private') -----
+ reposition
+ 	"Put ourself in the requested position on the display, but ensure completely within the bounds of the display"
+ 	| position |
+ 	self bounds:
+ 		((self fullBounds
+ 			align: self fullBounds center
+ 			with: (requestedPosition ifNil: [ self fullBounds center ])) translatedToBeWithin: Display boundingBox).
+ 	"Check to see if labels are wider than progress bars. In that case do
+ 	a centered instead of the default left aligned layout."
+ 	position := self width > (Inset x * 2 + (self borderWidth * 2) + BarWidth)
+ 		ifTrue: [ #topCenter ]
+ 		ifFalse: [ #leftCenter ].
+ 	self cellPositioning: position!

Item was changed:
  ----- Method: SystemProgressMorph>>setLabel:at: (in category 'labelling') -----
  setLabel: shortDescription at: slot
  	(labels at: slot) contents: shortDescription.
+ 	self reposition!
- 	self recenter!

Item was changed:
  ----- Method: SystemWindow>>openAsIsIn: (in category 'open/close') -----
  openAsIsIn: aWorld
  	"This msg and its callees result in the window being activeOnlyOnTop"
  	aWorld addMorph: self.
  	self activate.
  	aWorld startSteppingSubmorphsOf: self.
+ 	self activeHand releaseAllFoci!
- !

Item was changed:
  ----- Method: SystemWindow>>openInWorld: (in category 'open/close') -----
  openInWorld: aWorld
  	"This msg and its callees result in the window being activeOnlyOnTop"
  	self anyOpenWindowLikeMe
  		ifEmpty: 
  			[ self 
  				bounds: (RealEstateAgent initialFrameFor: self world: aWorld) ;
  				openAsIsIn: aWorld ]
  		ifNotEmptyDo:
  			[ : windows | 
  			windows anyOne
  				expand ;
  				activate ; 
+ 				postAcceptBrowseFor: self ].
+ 	self activeHand releaseAllFoci!
- 				postAcceptBrowseFor: self ]!

Item was changed:
  ----- Method: TextEditor>>browseClassFromIt (in category 'menu messages') -----
  browseClassFromIt
  	"Launch a hierarchy browser for the class indicated by the current selection.  If multiple classes matching the selection exist, let the user choose among them."
- 
  	| aClass |
+ 	self lineSelectAndEmptyCheck: [ ^ self ].
+ 	aClass := Utilities
+ 		classFromPattern: self selection string withBlanksTrimmed
+ 		withCaption: 'choose a class to browse...'.
+ 	aClass ifNil: [ ^ morph flash ].
+ 	SystemNavigation default
+ 		spawnHierarchyForClass: aClass
+ 		selector: nil!
- 	self lineSelectAndEmptyCheck: [^ self].
- 
- 	aClass := Utilities classFromPattern: (self selection string copyWithout: Character cr) withCaption: 'choose a class to browse...'.
- 	aClass ifNil: [^ morph flash].
- 
- 	SystemNavigation default spawnHierarchyForClass: aClass selector: nil!

Item was changed:
  ----- Method: TextEditor>>referencesToIt (in category 'menu messages') -----
  referencesToIt
  	"Open a MessageSet with the references to the selected global or variable name."
- 
  	| selection environment binding |
+ 	self selection isEmpty ifTrue: [ self selectWord ].
- 	self selectWord.
  	environment := (model respondsTo: #selectedClassOrMetaClass)
  		ifTrue: [ model selectedClassOrMetaClass ifNil: [ Smalltalk globals ] ]
  		ifFalse: [ Smalltalk globals ].
  	selection := self selectedSymbol ifNil: [ self selection asString ].
+ 	(environment isBehavior and:
+ 		[ (environment
+ 			instVarIndexFor: selection
+ 			ifAbsent: [ 0 ]) ~= 0 ]) ifTrue: [ ^ self systemNavigation
+ 			browseAllAccessesTo: selection
+ 			from: environment ].
+ 	selection isSymbol ifFalse: [ ^ morph flash ].
+ 	binding := (environment bindingOf: selection) ifNil: [ ^ morph flash ].
- 	(environment isBehavior and: [ 
- 		(environment instVarIndexFor: selection ifAbsent: [ 0 ]) ~= 0 ]) ifTrue: [ 
- 			^self systemNavigation browseAllAccessesTo: selection from: environment ].
- 	selection isSymbol ifFalse: [ ^morph flash ].
- 	binding := (environment bindingOf: selection) ifNil: [ ^morph flash ].
  	self systemNavigation browseAllCallsOn: binding!



More information about the Packages mailing list