[Pkg] The Trunk: EToys-nice.82.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 8 10:26:04 UTC 2011


Nicolas Cellier uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-nice.82.mcz

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

Name: EToys-nice.82
Author: nice
Time: 8 May 2011, 12:25:20.868 pm
UUID: b82489f5-9f58-4104-8e50-b731324dd722
Ancestors: EToys-nice.81

minor refactorings: use #anySatisfy: #allSatisfy: #noneSatisfy: where it simplifies

=============== Diff against EToys-nice.81 ===============

Item was changed:
  ----- Method: BooleanScriptEditor>>wantsDroppedMorph:event: (in category 'dropping/grabbing') -----
  wantsDroppedMorph: aMorph event: evt 
  	"Answer whether the receiver would be interested in accepting the morph"
  
+ 	(submorphs anySatisfy: [:m | m isAlignmentMorph]) 
+ 		ifTrue: [^ false].
- 	(submorphs detect: [:m | m isAlignmentMorph] ifNone: [nil]) 
- 		ifNotNil: [^ false].
  
  	((aMorph isKindOf: ParameterTile) and: [aMorph scriptEditor == self topEditor])
  		ifTrue: [^ true].
  	^ (aMorph isKindOf: PhraseTileMorph orOf: WatcherWrapper) 
  		and: [(#(#Command #Unknown) includes: aMorph resultType capitalized) not]!

Item was changed:
  ----- Method: EtoysPresenter>>reinvigorateAllScriptsTool: (in category 'playerList') -----
  reinvigorateAllScriptsTool: anAllScriptsTool 
  	"Rebuild the contents of an All Scripts tool"
  
  	| showingOnlyActiveScripts candidateList firstTwo oldList allExtantPlayers newList morphList |
  	showingOnlyActiveScripts := anAllScriptsTool showingOnlyActiveScripts.
  	self flushPlayerListCache.
  	"needed? Probably to pick up on programmatical script-status control only"
  
  	firstTwo := {anAllScriptsTool submorphs first.  anAllScriptsTool submorphs second}.
  	oldList := (anAllScriptsTool submorphs copyFrom: 3 to: anAllScriptsTool submorphs size) collect:
  		[:aRow |
  			(aRow findA: UpdatingSimpleButtonMorph) target].
  
  	allExtantPlayers := self allExtantPlayers.
  	anAllScriptsTool showingAllInstances "take all instances of all classes"
  		ifTrue:
  			[candidateList := allExtantPlayers]  
  
  		ifFalse:  "include only one exemplar per uniclass.  Try to get one that has some qualifying scripts"
  			[candidateList := Set new.
  			allExtantPlayers do:
  				[:aPlayer |
+ 					(candidateList noneSatisfy: [:plyr | plyr isMemberOf: aPlayer class]) ifTrue:
- 					(candidateList detect: [:plyr | plyr isMemberOf:  aPlayer class] ifNone: [nil]) ifNil:
  						[aPlayer instantiatedUserScriptsDo: [:aScriptInstantiation |
  							(showingOnlyActiveScripts not or: [aScriptInstantiation pausedOrTicking]) 								ifTrue:
  									[candidateList add: aPlayer]]]]].
  	newList := OrderedCollection new.
  	candidateList do:
  		[:aPlayer | aPlayer instantiatedUserScriptsDo:
  			[:aScriptInstantiation |
  				(showingOnlyActiveScripts not or: [aScriptInstantiation pausedOrTicking]) ifTrue:
  					[newList add: aScriptInstantiation]]].
  
  	oldList asSet = newList asSet
  		ifFalse:
  			[anAllScriptsTool removeAllMorphs; addAllMorphs: firstTwo.
  			morphList := newList collect:
  				[:aScriptInstantiation |  aScriptInstantiation statusControlRowIn: anAllScriptsTool].
  			anAllScriptsTool addAllMorphs: morphList.
  			newList do:
  				[:aScriptInstantiation | aScriptInstantiation updateAllStatusMorphs]]!

Item was changed:
  ----- Method: StandardViewer>>hasDismissButton (in category 'user interface') -----
  hasDismissButton
  	submorphs isEmptyOrNil ifTrue: [^ false].
+ 	^submorphs first allMorphs anySatisfy:
+ 		[:possible |  (possible isKindOf: SimpleButtonMorph) and: [possible actionSelector == #dismiss]]!
- 	^ (submorphs first allMorphs detect:
- 		[:possible |  (possible isKindOf: SimpleButtonMorph) and: [possible actionSelector == #dismiss]]
- 			ifNone: [nil]) notNil!

Item was changed:
  ----- Method: SyntaxMorph>>structureMatchWith: (in category 'dropping/grabbing') -----
  structureMatchWith: aMorph
  	| meNoun itNoun |
  	"Return true if the node types would allow aMorph to replace me.  This tests the gross structure of the method only."
  
  	meNoun := self isNoun.
  	itNoun := aMorph isNoun.
  
  	"Consider these nouns to be equal:  TempVariableNode, LiteralNode, VariableNode, (MessageNode with receiver), CascadeNode, AssignmentNode"
  	meNoun & itNoun ifTrue: [^ true].
  	meNoun & aMorph isBlockNode ifTrue: [^ true].
  
  	"If I am a BlockNode, and it is a TempVariableNode, add it into list"
  	"If I am a BlockNode, and it is a noun, add it as a new line"
  	self isBlockNode ifTrue:
  		[itNoun ifTrue: [^ true].
  		(aMorph nodeClassIs: ReturnNode) ifTrue:
+ 			[^ self submorphs
+ 				noneSatisfy: [:mm | (mm isSyntaxMorph) and: [mm nodeClassIs: ReturnNode]]].	"none already in this block"
- 			[^ (self submorphs
- 				detect: [:mm | ((mm isSyntaxMorph) and: [mm nodeClassIs: ReturnNode])]
- 				ifNone: [nil]) isNil].	"none already in this block"
  				"If I am a BlockNode, and it is a ReturnNode, add to end"
  		(aMorph nodeClassIs: CommentNode) ifTrue: [^ true]].
  
  	(self isMethodNode) ifTrue: [^ false].	"Later add args and keywords"
  		"Later allow comments to be dropped in"
  		"Add MethodTemps by dropping into the main block"
  
  	(self nodeClassIs: ReturnNode) & (aMorph parseNode class == MessageNode) 
  		ifTrue: [^ true].		"Command replace Return"
  	(self nodeClassIs: MessageNode) & (aMorph parseNode class == ReturnNode) ifTrue: [
  		(owner submorphs select: [:ss | ss isSyntaxMorph]) last == self
  			ifTrue: [^ true]].	"Return replace last command"
  
  	(aMorph nodeClassIs: AssignmentNode) ifTrue: [
  		itNoun ifFalse: ["create a new assignment"
  			^ self isAVariable & self isDeclaration not]].	"only assign to a variable"
  
  	"If nodes are of equal class, replace me with new one."
  	(self nodeClassIs: aMorph parseNode class) ifTrue: [
  		(self nodeClassIs: MessageNode) 
  				ifFalse: [^ true]	"normal match"
  				ifTrue: [^ self receiverNode == aMorph receiverNode]].	"both nil"
  
+ 	^ false "otherwise reject"!
- 	^ false "otherwise reject"
- !



More information about the Packages mailing list