[etoys-dev] Etoys: Etoys-kfr.112.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Mar 3 10:12:10 EST 2012


Karl Ramberg uploaded a new version of Etoys to project Etoys:
http://source.squeak.org/etoys/Etoys-kfr.112.mcz

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

Name: Etoys-kfr.112
Author: kfr
Time: 3 March 2012, 4:12:28 pm
UUID: 8aec26d2-e05b-9b42-8e49-e33b5bfdbfd9
Ancestors: Etoys-Richo.111

Following watchers
http://tracker.squeakland.org/browse/SQ-1029

add "attached watchers": watcher variants that behave as if "attached" to the object they are observing. Unlabeled and labeled versions are available. from both the halo-menu and the viewer of an attached watcher, one can configure where it should attach to the observed (e.g. left, topLeft, top, etc...) and how much it should be offset from the nominal attachment position.

=============== Diff against Etoys-Richo.111 ===============

Item was changed:
  ----- Method: DataType>>addWatcherItemsToMenu:forGetter: (in category '*Etoys-tiles') -----
  addWatcherItemsToMenu: aMenu forGetter: aGetter
  	"Add watcher items to the menu if appropriate, provided the getter is not an odd-ball one for which a watcher makes no sense"
  
  	(Vocabulary gettersForbiddenFromWatchers includes: aGetter) ifFalse:
  		[aMenu add: 'simple watcher' translated selector: #tearOffUnlabeledWatcherFor: argument: aGetter.
  		aMenu add: 'detailed watcher' translated selector: #tearOffFancyWatcherFor: argument: aGetter.
+ 		aMenu add: 'attached watcher' translated selector: #tearOffAttachedWatcherFor: argument: aGetter.
+ 		aMenu add: 'attached labeled watcher' translated selector: #tearOffAttachedLabeledWatcherFor: argument: aGetter.
  		aMenu addLine]!

Item was added:
+ WatcherWrapper subclass: #FollowingWatcher
+ 	instanceVariableNames: 'attachmentEdge offset'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Etoys-Scripting Support'!
+ 
+ !FollowingWatcher commentStamp: 'sw 2/13/2012 18:55' prior: 0!
+ A watcher that follows its watchee around.
+ 
+ attachmentEdge:  can be #left, #right #bottom, #top, or #bottomRight.
+ (missing items could obviously be added trivially if wanted)
+ 
+ offset:  (x,y) offset from the nominal attachment point.!

Item was added:
+ ----- Method: FollowingWatcher class>>additionsToViewerCategories (in category 'scripting') -----
+ additionsToViewerCategories
+ 	"Answer a list of (<categoryName> <list of category specs>) pairs that characterize the phrases this kind of morph wishes to add to various Viewer categories."
+ 
+ 	^ #((basic (
+ 			(slot attachmentOffset  'the amounts by which the position of the watcher should be offset from the nominal attachment point' Point readWrite Player getAttachmentOffset  Player  setAttachmentOffset:)
+ 			(slot attachmentEdge  'The attachment edge -- which edge or corner the watcher should be aligned with' AttachmentEdge readWrite Player getAttachmentEdge  Player  setAttachmentEdge:) 
+ )))!

Item was added:
+ ----- Method: FollowingWatcher>>addCustomMenuItems:hand: (in category 'accessing') -----
+ addCustomMenuItems: aMenu hand: aHand
+ 	"Add morph-specific items to a menu."
+ 
+ 	aMenu addUpdating:  #attachmentEdgeString  action: #chooseAttachmentEdge.
+ 	aMenu add: ('offset' translated, ' (', 'currently' translated, ' ', offset printString, ')') action: #chooseOffset!

Item was added:
+ ----- Method: FollowingWatcher>>attachmentEdge (in category 'accessing') -----
+ attachmentEdge
+ 	"Answer the value of attachmentEdge"
+ 
+ 	^ attachmentEdge!

Item was added:
+ ----- Method: FollowingWatcher>>attachmentEdge: (in category 'accessing') -----
+ attachmentEdge: anObject
+ 	"Set the value of attachmentEdge"
+ 
+ 	attachmentEdge := anObject!

Item was added:
+ ----- Method: FollowingWatcher>>attachmentEdgeString (in category 'accessing') -----
+ attachmentEdgeString
+ 	"Answer a string to serve as the wording of the menu item inviting the use to choose the attachment edge."
+ 
+ 	^ 'choose attachment edge'  translated, ' (', 'now' translated, ' ', attachmentEdge asString translated, ')'!

Item was added:
+ ----- Method: FollowingWatcher>>attachmentOffset (in category 'accessing') -----
+ attachmentOffset
+ 	"Answer the amount by which the watcher should be offset from its nominal attachment point near the watchee."
+ 
+ 	^ offset!

Item was added:
+ ----- Method: FollowingWatcher>>attachmentOffset: (in category 'accessing') -----
+ attachmentOffset: anAmount
+ 	"Set the amount by which the watcher should be offset from its nominal attachment point near the watchee."
+ 
+ 	offset := anAmount!

Item was added:
+ ----- Method: FollowingWatcher>>buildForPlayer:getter: (in category 'initialization') -----
+ buildForPlayer: aPlayer getter: aGetter 
+ 	"Build up basic structure"
+ 
+ 	super buildForPlayer: aPlayer getter: aGetter.
+ 	self firstSubmorph beTransparent; borderWidth: 0.
+ 	self beTransparent; borderWidth: 0!

Item was added:
+ ----- Method: FollowingWatcher>>buildReadout: (in category 'initialization') -----
+ buildReadout: aGetter
+ 	"Build and answer a readout for the given getter."
+ 
+ 	| readout |
+ 	readout := super buildReadout: aGetter.
+ 	((readout submorphs size > 0) and: [readout firstSubmorph isKindOf: StringMorph]) ifTrue:
+ 		[readout firstSubmorph font: ScriptingSystem fontForAttachedWatchers; unlock].
+ 	^ readout!

Item was added:
+ ----- Method: FollowingWatcher>>burnishForReplacing (in category 'copying') -----
+ burnishForReplacing
+ 	"Final appearance modifications before the receiver is inserted as a replacement for an earlier version of the watcher. "
+ 
+ 	self allMorphsDo: [:m | (m isKindOf: StringMorph) ifTrue: [m font: ScriptingSystem fontForAttachedWatchers]]!

Item was added:
+ ----- Method: FollowingWatcher>>chooseAttachmentEdge (in category 'accessing') -----
+ chooseAttachmentEdge
+ 	"Put up a menu allowing the user to choose which edge of the object being watched the receiver should attach itself to."
+ 
+ 	| choice |
+ 	choice := (SelectionMenu selections: #(top topRight right bottomRight  bottom bottomLeft left topLeft center)) startUpWithCaption: ('attachment edge
+ currently: ', attachmentEdge translated).
+ 	choice isEmptyOrNil ifFalse:
+ 		[self attachmentEdge: choice]!

Item was added:
+ ----- Method: FollowingWatcher>>chooseOffset (in category 'accessing') -----
+ chooseOffset
+ 	"Allow the user to select a new offset to apply to the positioning of the receiver with respect to the object it follows."
+ 
+ 	| result aPoint |
+ 	result := FillInTheBlank request: 'offset' translated initialAnswer: offset printString.
+ 	result isEmptyOrNil ifTrue: [^ self].
+ 	aPoint := [Compiler evaluate: result] on: Error do: [^ self inform: 'error' translated].
+ 	(aPoint isKindOf: Point) ifFalse: [^ self inform: 'error' translated].
+ 	offset := aPoint!

Item was added:
+ ----- Method: FollowingWatcher>>fancyForPlayer:getter: (in category 'initialization') -----
+ fancyForPlayer: aPlayer getter: aGetter 
+ 	"Configure the receiver to be a 'following' watcher labeled with the variable name but not with the player name."
+ 
+ 	| aLabel |
+ 	self buildForPlayer: aPlayer getter: aGetter.
+ 	aLabel := StringMorph contents: variableName translated , ' = ' font: ScriptingSystem fontForAttachedWatchers.
+ 	aLabel setProperty: #watcherLabel toValue: true.
+ 	self addMorphFront: aLabel!

Item was added:
+ ----- Method: FollowingWatcher>>initialize (in category 'accessing') -----
+ initialize
+ 	"Initialize the receiver."
+ 
+ 	super initialize.
+ 	attachmentEdge := #bottom.
+ 	offset := 0 at 0!

Item was added:
+ ----- Method: FollowingWatcher>>openInWorld (in category 'initialization') -----
+ openInWorld
+ 	"Open the receiver near the watchee, but if possible avoiding attached-watcher locations already in use."
+ 
+ 	| aMorph others |
+ 	super openInWorld.
+ 	self allMorphsDo: [:m | (m isKindOf: StringMorph) ifTrue: [m font: ScriptingSystem fontForAttachedWatchers]].
+ 	(aMorph := player costume) isInWorld ifTrue:
+ 		[others := aMorph owner submorphs
+ 			select:
+ 				[:m | m ~~ self and: [m isKindOf: self class] and: [m associatedPlayer == player]]
+ 			thenCollect:
+ 				[:m | m attachmentEdge].
+ 		attachmentEdge := #(bottom left top right topLeft topRight bottomRight bottomLeft) detect:
+ 			[:edge | (others includes: edge) not] ifNone: [#bottom]]!

Item was added:
+ ----- Method: FollowingWatcher>>prospectiveReplacement (in category 'copying') -----
+ prospectiveReplacement
+ 	"Answer another watcher of the same class which will serve as the replacement for the receiver.  This is used when the whole apparatus needs to be rebuilt after, for example, a type change or a name change."
+ 
+ 	| replacement |
+ 	replacement := super prospectiveReplacement.
+ 	replacement attachmentEdge: attachmentEdge.
+ 	replacement attachmentOffset: offset.
+ 	^ replacement!

Item was added:
+ ----- Method: FollowingWatcher>>step (in category 'stepping') -----
+ step
+ 	"Periodic activity:  follow watchee round."
+ 
+ 	| itsCostume morphToMove itsPlayfield |
+ 	super step.
+ 	(itsCostume := player costume) isInWorld ifTrue:
+ 		[((morphToMove := self topRendererOrSelf) owner == (itsPlayfield := itsCostume owner))  ifFalse:
+ 			[itsPlayfield addMorphFront: morphToMove].
+ 		morphToMove center: itsCostume center.
+ 
+ 		(#(bottomLeft bottom bottomRight) includes: attachmentEdge) ifTrue:
+ 			[morphToMove top: itsCostume bottom].
+ 		(#(topLeft top topRight) includes: attachmentEdge) ifTrue:
+ 			[morphToMove bottom: itsCostume top].
+ 		(#(topLeft left bottomLeft) includes: attachmentEdge) ifTrue:
+ 			[morphToMove right: itsCostume left].
+ 		(#(topRight right bottomRight) includes: attachmentEdge) ifTrue:
+ 			[morphToMove left: itsCostume right].
+ 
+ 		morphToMove position: (morphToMove position + offset)]!

Item was added:
+ ----- Method: FollowingWatcher>>unlabeledForPlayer:getter: (in category 'initialization') -----
+ unlabeledForPlayer: aPlayer getter: aGetter 
+ 	"build a simple watcher"
+ 
+ 	| readout |
+ 	self buildForPlayer: aPlayer getter: aGetter.
+ 	readout := self submorphs last.
+ 	(readout isKindOf: TileMorph)
+ 		ifTrue: [readout labelMorph lock: true.
+ 			readout labelMorph font: ScriptingSystem fontForAttachedWatchers.
+ 			readout labelMorph beSticky]!

Item was changed:
  ----- Method: Player>>changeTypesInWatchersOf: (in category 'translation') -----
  changeTypesInWatchersOf: slotName
  	"The type of a variable has changed; adjust watchers to that fact."
  
  	| aGetter newWatcher |
  	aGetter _ Utilities getterSelectorFor: slotName.
  	self allPossibleWatchersFromWorld do: [:aWatcher |
  		(aWatcher getSelector = aGetter) ifTrue:
  			[(aWatcher ownerThatIsA: WatcherWrapper) ifNotNilDo:
  				[:aWrapper |
  					newWatcher _ (aWrapper submorphs size = 1)
  						ifTrue:
+ 							[aWrapper prospectiveReplacement unlabeledForPlayer: self getter: aGetter]
- 							[WatcherWrapper new unlabeledForPlayer: self getter: aGetter]
  						ifFalse:
+ 							[aWrapper prospectiveReplacement fancyForPlayer: self getter: aGetter].
+ 					newWatcher burnishForReplacing.
- 							[WatcherWrapper new fancyForPlayer: self getter: aGetter].
- 					newWatcher position: aWatcher position.
  					aWrapper owner replaceSubmorph: aWrapper by: newWatcher]]]
  !

Item was added:
+ ----- Method: Player>>getAttachmentEdge (in category 'slot getters/setters') -----
+ getAttachmentEdge
+ 	"Answer the attachment edge, a point."
+ 
+ 	^ costume renderedMorph attachmentEdge!

Item was added:
+ ----- Method: Player>>getAttachmentOffset (in category 'slot getters/setters') -----
+ getAttachmentOffset
+ 	"Answer the attachment offset, a point."
+ 
+ 	^ costume renderedMorph attachmentOffset!

Item was added:
+ ----- Method: Player>>setAttachmentEdge: (in category 'slot getters/setters') -----
+ setAttachmentEdge: aSymbol
+ 	"Set the attachment edge to the given symbol"
+ 
+ 	^ costume renderedMorph attachmentEdge: aSymbol!

Item was added:
+ ----- Method: Player>>setAttachmentOffset: (in category 'slot getters/setters') -----
+ setAttachmentOffset: aPoint
+ 	"Set the attachment offset, a point"
+ 
+ 	^ costume renderedMorph attachmentOffset: aPoint!

Item was added:
+ ----- Method: Player>>tearOffAttachedLabeledWatcherFor: (in category 'slots-user') -----
+ tearOffAttachedLabeledWatcherFor: aGetter 
+ 	"Open a following watcher for the given getter."
+ 
+ 	(FollowingWatcher new fancyForPlayer: self getter: aGetter) openInWorld!

Item was added:
+ ----- Method: Player>>tearOffAttachedWatcherFor: (in category 'slots-user') -----
+ tearOffAttachedWatcherFor: aGetter 
+ 	"Open a following watcher for the given getter."
+ 
+ 	(FollowingWatcher new unlabeledForPlayer: self getter: aGetter) openInWorld!

Item was added:
+ ----- Method: StandardScriptingSystem>>fontForAttachedWatchers (in category '*Etoys-font & color choices') -----
+ fontForAttachedWatchers
+ 	"Answer the font to use in following watchers"
+ 
+ 	^ StrikeFont familyName: 'BitstreamVeraSerif' size: 16!

Item was added:
+ ----- Method: WatcherWrapper>>burnishForReplacing (in category 'copying') -----
+ burnishForReplacing
+ 	"Final appearance modifications before the receiver is inserted as a replacement for an earlier version of the watcher.  This is a hook so that the FollowingWatcher has a chance to get its fonts right."!

Item was added:
+ ----- Method: WatcherWrapper>>prospectiveReplacement (in category 'copying') -----
+ prospectiveReplacement
+ 	"Answer another watcher of the same class which will serve as the replacement for the receiver.  This is used when the whole apparatus needs to be rebuilt after, for example, a type change or a name change."
+ 
+ 	| replacement |
+ 	replacement := self class new.
+ 	replacement position: self position.
+ 	^ replacement!

Item was added:
+ ----- Method: WatcherWrapper>>variableName (in category 'accessing') -----
+ variableName
+ 	"Answer the name of the variable being watched."
+ 
+ 	^ variableName!



More information about the etoys-dev mailing list