[squeak-dev] The Inbox: EToys-jl.230.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 1 09:00:46 UTC 2016


A new version of EToys was added to project The Inbox:
http://source.squeak.org/inbox/EToys-jl.230.mcz

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

Name: EToys-jl.230
Author: jl
Time: 1 September 2016, 10:59:46.740946 am
UUID: 06b0aa06-1a5f-f64b-a0fa-d9b063894041
Ancestors: EToys-jl.226, EToys-nice.229

merged again

=============== Diff against EToys-jl.226 ===============

Item was changed:
  ----- Method: ChessBoard class>>initializeHashKeys (in category 'class initialization') -----
  initializeHashKeys
  	"ChessGame initialize"
  	| random |
  	HashKeys := Array new: 12.
  	1 to: HashKeys size do:[:i| HashKeys at: i put: (WordArray new: 64)].
  	HashLocks := Array new: 12.
  	1 to: HashLocks size do:[:i| HashLocks at: i put: (WordArray new: 64)].
  	random := Random seed: 23648646.
  	1 to: 12 do:[:i|
  		1 to: 64 do:[:j|
+ 			(HashKeys at: i) at: j put: (random nextInt: 16r3FFFFFFF "SmallInteger maxVal on 32bits VM")- 1. 
+ 			(HashLocks at: i) at: j put: (random nextInt: 16r3FFFFFFF "SmallInteger maxVal on 32bits VM") - 1.
- 			(HashKeys at: i) at: j put: (random nextInt: SmallInteger maxVal) - 1.
- 			(HashLocks at: i) at: j put: (random nextInt: SmallInteger maxVal) - 1.
  		].
  	].
  
  !

Item was changed:
  ----- Method: KedamaExamplerPlayer>>containsSequentialSelector: (in category '*Etoys-Squeakland-private') -----
  containsSequentialSelector: aSymbol
  
+ 	^ (#(random random: atRandom) includes: aSymbol)!
- 	^ (#(random random:) includes: aSymbol)!

Item was changed:
  ----- Method: KedamaMorph>>dimensions: (in category 'accessing') -----
  dimensions: anExtent
  	dimensions := anExtent.
  	wrapX := dimensions x asFloat.
  	wrapY := dimensions y asFloat.
  	patchVarDisplayForm := Form extent: dimensions depth: 32.
  	patchesToDisplay ifNotNil: [
  		patchesToDisplay do: [ :ea |
  			ea newExtent: anExtent.
  		].
  	].
  	self pixelsPerPatch: self pixelsPerPatch.!

Item was changed:
  ----- Method: KedamaMorph>>drawTurtlesOnForm: (in category 'drawing') -----
  drawTurtlesOnForm: aForm
  
  	turtlesToDisplay do: [:exampler |
  		(self isVisible: exampler) ifTrue: [
  			turtlesDictSemaphore critical: [
  				exampler turtles drawOn: aForm.
+ 			] ifLocked: []
- 			].
  		].
  	].
  !

Item was changed:
  ----- Method: KedamaTurtleMethodAttributionDefinition2 class>>determineStatementType:fromDict:primaryBreedPair:messageType:isStatement:receiverObject: (in category 'rules') -----
  determineStatementType: parentStmtType fromDict: dict primaryBreedPair: myPrimaryBreedPair messageType: myMessageType isStatement: myIsStatement receiverObject: myReceiverObject
  
  	| vectorTurtle turtleSelectors participants reads writes unknownReceiverSelectors |
  		"Do the calculation only at the statement level."
  	myIsStatement ifFalse: [^ parentStmtType].
  		"If there is a doSequentially: block, the block is sequential."
  
  	participants := dict at: self.
  	(participants select: [:e | (e first notNil and: [e first isPrototypeTurtlePlayer])]) size = 0 ifTrue: [^ #none].
  	myMessageType = #sequential ifTrue: [^ #sequential].
  
  	parentStmtType = #sequential ifTrue: [^ #sequential].
  
  	"If there is not turtle involved in the statement, it is not transformed."
  	myPrimaryBreedPair ifNil: [^ #none].
  
  
  	vectorTurtle := myPrimaryBreedPair first.
  	myMessageType = #condition ifTrue: [
  		reads := IdentitySet new.
  		writes := IdentitySet new.
  	
  		participants do: [:list |
  			(((list at: 5) = #testBody or: [(list at: 5) = #testCond]) and: [(list at: 4) ~= #read]) ifTrue: [list first ifNotNil: [writes add: list first]].
  			(((list at: 5) = #testBody or: [(list at: 5) = #testCond]) and: [(list at: 4) = #read]) ifTrue: [list first ifNotNil: [reads add: list first]].
  		].
  		((writes
  			intersection: reads)
  				copyWithout: vectorTurtle) ifNotEmpty: [
  					^ #sequential
  		].
  		^ #parallel.
  	].
  
  	reads := IdentitySet new.
  	writes := IdentitySet new.
  	turtleSelectors := OrderedCollection new.
  	unknownReceiverSelectors := OrderedCollection new.
  	participants do: [:list |
  		list first = vectorTurtle ifTrue: [
  			((vectorTurtle isBreedSelector: list second) or: [
  				(vectorTurtle isUserDefinedSelector: list second)]) ifFalse: [
  					turtleSelectors add: list second
  			].
  		].
  		list first
  			ifNil: [unknownReceiverSelectors add: list second]
  			ifNotNil: [
  				((list at: 4) == #read) ifTrue: [reads add: list first].
  				((list at: 4) == #read) ifFalse: [writes add: list first].
  			].
  		(vectorTurtle containsSequentialSelector: list second) ifTrue: [^ #sequential].
  	].
  	(turtleSelectors includes: #die) ifTrue: [^ #die].
  	(((self isKindOf: AssignmentNode) and: [myReceiverObject = vectorTurtle])
  		and: [vectorTurtle isBreedSelector: self property property]) ifTrue: [^ #none].
  
  	(vectorTurtle areOkaySelectors: unknownReceiverSelectors) ifFalse: [
  		^ #sequential.
  	].
  
  	(vectorTurtle vectorizableTheseSelectors: turtleSelectors) ifFalse: [^ #sequential].
  	((reads intersection: writes) copyWithout: vectorTurtle) ifNotEmpty: [^ #sequential].
+ 
+ 	"Check the hard way. If any leaf nodes"
+ 	self nodesDo: [:node |
+ 		(node isMessageNode and: [vectorTurtle containsSequentialSelector: node selector])
+ 			ifTrue: [^ #sequential]].
+ 	
  	^ #parallel.
  
  !

Item was changed:
  ----- Method: KedamaTurtleVectorPlayer2>>test:ifTrue:ifFalse: (in category 'command execution') -----
  test: cond ifTrue: trueBlock ifFalse: falseBlock
  
+ 	| origPredicate c actualCond |
- 	| origPredicate c |
  	(cond == true or: [cond == false]) ifTrue: [
  		^ cond ifTrue: [trueBlock value: self] ifFalse: [falseBlock value: self].
  	].
+ 	actualCond := cond.
+ 	cond isBlock ifTrue: [
+ 		actualCond := ByteArray new: predicate size.
+ 		1 to: predicate size do: [:i | actualCond at: i put: (cond value ifTrue: [1] ifFalse: [0])]
+ 	].
  	origPredicate := predicate clone.
+ 	predicate bytesAnd: actualCond.
- 	predicate bytesAnd: cond.
  	trueBlock value: self.
  
+ 	c := actualCond clone.
- 	c := cond clone.
  	c not.
  	predicate replaceFrom: 1 to: (predicate size min: origPredicate size) with: origPredicate startingAt: 1.
  	predicate bytesAnd: c.
  	falseBlock value: self.
  	predicate replaceFrom: 1 to: (predicate size min: origPredicate size) with: origPredicate startingAt: 1.!

Item was changed:
  ----- Method: KedamaVectorParseTreeRewriter>>visit:andParent: (in category 'entry point') -----
  visit: node andParent: parent
  
  	| newNode possibleSelector selIndex parentRewriterBlock newNodeBlock |
  	node isLeaf not ifTrue: [
  		node getAllChildren do: [:child |
  			self visit: child andParent: node.
  		].
  	].
  
  	(node rewriteInfoOut notNil) ifTrue: [
  		((node isMemberOf: VariableNode) or: [node isMemberOf: LiteralVariableNode]) ifTrue: [
  			newNode := TempVariableNode new name: node rewriteInfoOut second index: 0 type: 2.
  			parent replaceNode: node with: newNode.
  		].
  	].
  
  	(node isMemberOf: MessageNode) ifTrue: [
  		(node statementType = #sequential) ifTrue: [
  			node selector key = #doSequentialCommand: ifTrue: [
  				(node isStatement) ifTrue: [
  					node receiver: node primaryBreedPair second.
  				].
  			]
  		].
  	].
  
  	(node isMemberOf: MessageNode) ifTrue: [		
  		newNodeBlock := [:selector :args |
  			self
  				createMessageNode: node
  				inParentNode: parent
  				receiverNode: (TempVariableNode new name: node rewriteInfoOut second index: 0 type: 2) 
  				selector: selector
  				arguments: args].									
  
  		((selIndex := #(parallel sequential die) indexOf: node statementType) > 0) ifTrue: [
  			possibleSelector := #(doCommand: doSequentialCommand: doDieCommand:) at: selIndex.
  			
  			parentRewriterBlock := [:newNod |
  			self
  				rewriteMessageNode: node
  				inParentNode: parent
  				receiverNode: node rewriteInfoIn second
  				selector: possibleSelector
  				arguments: {self
  									makeBlockNodeArguments: {node rewriteInfoOut second}
  									statements: {newNod} returns: false}].
  			
  			(node messageType = #condition) ifTrue: [
  				newNode := newNodeBlock
  									value: #test:ifTrue:ifFalse:
+ 									value: {BlockNode withJust: node receiver. node arguments first. node arguments second}.
- 									value: {node receiver. node arguments first. node arguments second}.
  				(node isStatement) ifFalse: [
  					parent replaceNode: node with: newNode.
  				] ifTrue: [
  					parentRewriterBlock value: newNode.
  				].
  			] ifFalse: [
  				node selector key = #timesRepeat:
  					ifTrue: [
  						newNode := newNodeBlock
  											value: #times:repeat:
  											value: {node receiver. node arguments first}.
  						(node isStatement) ifFalse: [
  							parent replaceNode: node with: newNode.
  						] ifTrue: [
  							parentRewriterBlock value: newNode.
  						].
  					]
  					ifFalse: [(node isStatement) ifTrue: [
  						parentRewriterBlock value: node
  					].
  				].
  			]
  		].
  	].
  
  	(node isMemberOf: BlockNode) ifTrue: [
  		(node rewriteInfoOut notNil) ifTrue: [
  			self rewriteBlockNode: node inParentNode: parent arguments: (Array with: (TempVariableNode new name: node rewriteInfoOut second index: 0 type: 2)) statements: node statements returns: false.
  		].
  	].
  
  !

Item was changed:
  ----- Method: MessageAsTempNode>>determineStatementType:fromDict:primaryBreedPair:messageType:isStatement:receiverObject: (in category '*Etoys-Tweak-Kedama-Generated') -----
  determineStatementType: t1 fromDict: t2 primaryBreedPair: t3 messageType: t4 isStatement: t5 receiverObject: t6 
  	| t7 t8 t9 t10 t11 t13 |
  	t5
  		ifFalse: [^ t1].
  	t9 := t2 at: self.
  	(t9
  			select: [:t14 | t14 first notNil
  					and: [t14 first isPrototypeTurtlePlayer]]) size = 0
  		ifTrue: [^ #none].
  	t4 = #sequential
  		ifTrue: [^ #sequential].
  	t1 = #sequential
  		ifTrue: [^ #sequential].
  	t3
  		ifNil: [^ #none].
  	t7 := t3 first.
  	t4 = #condition
  		ifTrue: [t11 := IdentitySet new.
  			t13 := IdentitySet new.
  			t9
  				do: [:t14 | 
  					(((t14 at: 5)
  									= #testBody
  								or: [(t14 at: 5)
  										= #testCond])
  							and: [(t14 at: 4)
  									~= #read])
  						ifTrue: [t14 first
  								ifNotNil: [t13 add: t14 first]].
  					(((t14 at: 5)
  									= #testBody
  								or: [(t14 at: 5)
  										= #testCond])
  							and: [(t14 at: 4)
  									= #read])
  						ifTrue: [t14 first
  								ifNotNil: [t11 add: t14 first]]].
  			((t13 intersection: t11)
  				copyWithout: t7)
  				ifNotEmpty: [^ #sequential].
  			^ #parallel].
  	t11 := IdentitySet new.
  	t13 := IdentitySet new.
  	t8 := OrderedCollection new.
  	t10 := OrderedCollection new.
  	t9
  		do: [:t14 | 
  			t14 first = t7
  				ifTrue: [((t7 isBreedSelector: t14 second)
  							or: [t7 isUserDefinedSelector: t14 second])
  						ifFalse: [t8 add: t14 second]].
  			t14 first
  				ifNil: [t10 add: t14 second]
  				ifNotNil: [(t14 at: 4)
  							== #read
  						ifTrue: [t11 add: t14 first].
  					(t14 at: 4)
  							== #read
  						ifFalse: [t13 add: t14 first]].
  			(t7 containsSequentialSelector: t14 second)
  				ifTrue: [^ #sequential]].
  	(t8 includes: #die)
  		ifTrue: [^ #die].
  	(((self isKindOf: AssignmentNode)
  				and: [t6 = t7])
  			and: [t7 isBreedSelector: self property property])
  		ifTrue: [^ #none].
  	(t7 areOkaySelectors: t10)
  		ifFalse: [^ #sequential].
  	(t7 vectorizableTheseSelectors: t8)
  		ifFalse: [^ #sequential].
  	((t11 intersection: t13)
  		copyWithout: t7)
  		ifNotEmpty: [^ #sequential].
+ 	self
+ 		nodesDo: [:t14 | (t14 isLeaf
+ 					and: [t7 containsSequentialSelector: t14 key])
+ 				ifTrue: [^ #sequential]].
  	^ #parallel!

Item was changed:
  ----- Method: MessageNode>>determineStatementType:fromDict:primaryBreedPair:messageType:isStatement:receiverObject: (in category '*Etoys-Tweak-Kedama-Generated') -----
  determineStatementType: t1 fromDict: t2 primaryBreedPair: t3 messageType: t4 isStatement: t5 receiverObject: t6 
  	| t7 t8 t9 t10 t11 t13 |
  	t5
  		ifFalse: [^ t1].
  	t9 := t2 at: self.
  	(t9
  			select: [:t14 | t14 first notNil
  					and: [t14 first isPrototypeTurtlePlayer]]) size = 0
  		ifTrue: [^ #none].
  	t4 = #sequential
  		ifTrue: [^ #sequential].
  	t1 = #sequential
  		ifTrue: [^ #sequential].
  	t3
  		ifNil: [^ #none].
  	t7 := t3 first.
  	t4 = #condition
  		ifTrue: [t11 := IdentitySet new.
  			t13 := IdentitySet new.
  			t9
  				do: [:t14 | 
  					(((t14 at: 5)
  									= #testBody
  								or: [(t14 at: 5)
  										= #testCond])
  							and: [(t14 at: 4)
  									~= #read])
  						ifTrue: [t14 first
  								ifNotNil: [t13 add: t14 first]].
  					(((t14 at: 5)
  									= #testBody
  								or: [(t14 at: 5)
  										= #testCond])
  							and: [(t14 at: 4)
  									= #read])
  						ifTrue: [t14 first
  								ifNotNil: [t11 add: t14 first]]].
  			((t13 intersection: t11)
  				copyWithout: t7)
  				ifNotEmpty: [^ #sequential].
  			^ #parallel].
  	t11 := IdentitySet new.
  	t13 := IdentitySet new.
  	t8 := OrderedCollection new.
  	t10 := OrderedCollection new.
  	t9
  		do: [:t14 | 
  			t14 first = t7
  				ifTrue: [((t7 isBreedSelector: t14 second)
  							or: [t7 isUserDefinedSelector: t14 second])
  						ifFalse: [t8 add: t14 second]].
  			t14 first
  				ifNil: [t10 add: t14 second]
  				ifNotNil: [(t14 at: 4)
  							== #read
  						ifTrue: [t11 add: t14 first].
  					(t14 at: 4)
  							== #read
  						ifFalse: [t13 add: t14 first]].
  			(t7 containsSequentialSelector: t14 second)
  				ifTrue: [^ #sequential]].
  	(t8 includes: #die)
  		ifTrue: [^ #die].
  	(((self isKindOf: AssignmentNode)
  				and: [t6 = t7])
  			and: [t7 isBreedSelector: self property property])
  		ifTrue: [^ #none].
  	(t7 areOkaySelectors: t10)
  		ifFalse: [^ #sequential].
  	(t7 vectorizableTheseSelectors: t8)
  		ifFalse: [^ #sequential].
  	((t11 intersection: t13)
  		copyWithout: t7)
  		ifNotEmpty: [^ #sequential].
+ 	self
+ 		nodesDo: [:t14 | (t14 isLeaf
+ 					and: [t7 containsSequentialSelector: t14 key])
+ 				ifTrue: [^ #sequential]].
  	^ #parallel!

Item was added:
+ ----- Method: Morph>>boundsSignatureHash (in category '*Etoys') -----
+ boundsSignatureHash
+ 	"Answer a hash value that can be used to see if I've moved or been changed significantly"
+ 	^self boundsInWorld hash
+ !

Item was changed:
  ----- Method: SpeechBubbleMorph>>balloon (in category 'accessing') -----
  balloon
  	^balloon ifNil: [
  		| balloonForm |
+ 		balloonForm := Form extent: (self extent - (0 @ self tailHeight) max: 1 at 1) depth: 16.
- 		balloonForm := Form extent: self extent - (0 @ self tailHeight) depth: 16.
  		self drawBalloonOn: balloonForm getCanvas in: balloonForm boundingBox.
  		balloonForm floodFill: self color at: balloonForm center.
  		balloon := (SketchMorph withForm: balloonForm).
  	]!



More information about the Squeak-dev mailing list