[Pkg] The Trunk: EToys-tfel.220.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 31 11:11:59 UTC 2016


Tim Felgentreff uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-tfel.220.mcz

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

Name: EToys-tfel.220
Author: tfel
Time: 31 August 2016, 11:49:20.463793 am
UUID: a52ba16f-ef4a-cd49-bd51-c28b7e8b2dcf
Ancestors: EToys-tfel.219

- make it easy to set the Kedama dimensions from etoys
- register kedama particles in supplies

=============== Diff against EToys-tfel.219 ===============

Item was changed:
  ----- Method: KedamaMorph class>>additionsToViewerCategories (in category 'class initialization') -----
  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."
  	^ #(
  
   	(kedama (
  		(command addToPatchDisplayList: 'add patch to display list' Patch)
  		(command removeAllFromPatchDisplayList 'clear the patch display list')
  		(slot patchDisplayList 'patches to display' String readOnly Player getPatchesList unused unused)
  		(command addToTurtleDisplayList: 'add turtle to display list' Player)
  		(command removeAllFromTurtleDisplayList 'clear the turtle display list')
  		(slot turtleDisplayList 'turtles to display' String readOnly Player getTurtlesList unused unused)
  		(slot pixelsPerPatch 'the display scale' Number readWrite Player getPixelsPerPatch Player setPixelsPerPatch:)
+ 		(slot dimensions 'the turtles in x and y direction' Point readWrite Player getDimensions Player setDimensions:)
  		(slot color 'The color of the object' Color readWrite Player getColor  Player  setColor:)
  		"(command makeTurtlesMap 'Internally create the map of turtles')"
  		(slot leftEdgeMode 'the mode of left edge' EdgeMode readWrite Player getLeftEdgeMode Player setLeftEdgeMode:)
  		(slot rightEdgeMode 'the mode of right edge' EdgeMode readWrite Player getRightEdgeMode Player setRightEdgeMode:)
  		(slot topEdgeMode 'the mode of top edge' EdgeMode readWrite Player getTopEdgeMode Player setTopEdgeMode:)
  		(slot bottomEdgeMode 'the mode of bottom edge' EdgeMode readWrite Player getBottomEdgeMode Player setBottomEdgeMode:)
  	))
  ).
  !

Item was added:
+ ----- Method: KedamaMorph class>>registerInFlapsRegistry (in category 'as yet unclassified') -----
+ registerInFlapsRegistry
+ 	"Register the receiver in the system's flaps registry"
+ 	self environment
+ 		at: #Flaps
+ 		ifPresent: [:cl |
+ 			cl registerQuad: {
+ 					#KedamaMorph. #newSet. 'Particles' translatedNoop.
+ 					'A Kedama World with pre-made components' translatedNoop}
+ 				forFlapNamed: 'Supplies']!

Item was changed:
  ----- Method: KedamaMorph>>acceptForm: (in category 'event handling') -----
  acceptForm: aForm
  
  	| c xArray yArray colorArray newX newY turtlesByColor colorArrays thisPlayer xArrays yArrays |
  	turtlesDict keysAndValuesDo: [:player :vector |
  		player setTurtleCount: 0].
  	turtlesByColor := Dictionary new.
  	turtlesDict keysAndValuesDo: [:player :vector |
  		turtlesByColor at: player color put: player].
  	xArrays := Dictionary new.
  	yArrays := Dictionary new.
  	colorArrays := Dictionary new.
  	0 to: aForm height do: [:y |
  		0 to: aForm width do: [:x |
  			c := aForm colorAt: (x at y).
  			c isTransparent ifFalse: [
+ 				newX := x + aForm offset x.
+ 				newY := y + aForm offset y.
- 				newX := x.
- 				newY := y.
  				((newX >= 0 and: [newX < (self dimensions * pixelsPerPatch) x]) and: [newY >= 0 and: [newY < (self dimensions * pixelsPerPatch) y]]) ifTrue: [
  					thisPlayer := turtlesByColor at: c ifAbsentPut: [
  						turtlesByColor keys
  							detect: [:thisColor | (thisColor diff: c) < 0.2]
  							ifFound: [:thisColor | turtlesByColor at: thisColor]
  							ifNone: [
  								(self player newTurtleSilently color: c; player)]].
  					xArray := xArrays at: thisPlayer ifAbsentPut: [OrderedCollection new: aForm width * aForm height].
  					yArray := yArrays at: thisPlayer ifAbsentPut: [OrderedCollection new: aForm width * aForm height].
  					colorArray := colorArrays at: thisPlayer ifAbsentPut: [OrderedCollection new: aForm width * aForm height].
  
  					xArray add: newX asFloat / pixelsPerPatch.
  					yArray add: newY asFloat / pixelsPerPatch.
  					colorArray add: (c pixelValueForDepth: 32).
  				].
  			].
  		].
  	].
  	xArrays keysAndValuesDo: [:player :xArry |
  		self makeTurtlesAtPositionsIn: {xArry asArray. (yArrays at: player) asArray. (colorArrays at: player) asArray} examplerPlayer: player ofPrototype: nil.
  		player costume privateTurtleCount: (self turtlesCountOf: player)].!

Item was added:
+ ----- Method: KedamaMorph>>dimensions: (in category 'accessing') -----
+ dimensions: aPoint
+ 
+ 	dimensions := aPoint.
+ 	wrapX := dimensions x asFloat.
+ 	wrapY := dimensions y asFloat.
+ 	patchVarDisplayForm := Form extent: dimensions depth: 32.
+ 	self pixelsPerPatch: self pixelsPerPatch.!

Item was changed:
  ----- Method: KedamaMorph>>editDrawing (in category 'menu') -----
  editDrawing
  
  	| bnds sketchEditor delBlock myForm mySketch |
  	self world assureNotPaintingElse: [^self].
  	self world
  		prepareToPaint;
  		displayWorld.
  	bnds := self boundsInWorld.
  	sketchEditor := SketchEditorMorph new.
  	self comeToFront.
  	myForm := self imageForm clippedToSize: (bnds extent - 2).
  	myForm mapColor: self color to: Color transparent.
  	mySketch := SketchMorph withForm: myForm.
  	mySketch position: self position.
  	self world addMorphFront: sketchEditor.
  	sketchEditor 
  		initializeFor: mySketch
  		inBounds: bnds
  		pasteUpMorph: self world.
  	delBlock := [self world paintingFlapTab
  				ifNotNil: [:pt | pt hideFlap]
  				ifNil: [self world paintBox ifNotNil: [:pb | pb delete]]].
  	sketchEditor
  		afterNewPicDo: [:aForm :aRect |
+ 			aForm offset: aRect topLeft - self topLeft.
  			self acceptForm: aForm.
  			delBlock value]
  		ifNoBits: [delBlock value]!

Item was changed:
  ----- Method: KedamaMorph>>initialize (in category 'initialization') -----
  initialize
  
  	super initialize.
  	drawRequested := true.
  	changePending := false.
+ 	pixelsPerPatch := (World width min: World height) // (self class defaultDimensions x * 2). "heuristic..."
+ 	self dimensions: self class defaultDimensions.  "dimensions of this StarSqueak world in patches"
- 	dimensions := self class defaultDimensions.  "dimensions of this StarSqueak world in patches"
- 	wrapX := dimensions x asFloat.
- 	wrapY := dimensions y asFloat.
- 	pixelsPerPatch := (World width min: World height) // 200. "heuristic..."
  	super extent: dimensions * pixelsPerPatch.
  	self assuredPlayer assureUniClass.
  	self clearAll.  "be sure this is done once in case setup fails to do it"
  	autoChanged := true.
  	self leftEdgeMode: #wrap.
  	self rightEdgeMode: #wrap.
  	self topEdgeMode: #wrap.
  	self bottomEdgeMode: #wrap.
  
  	turtlesDictSemaphore := Semaphore forMutualExclusion.
  !

Item was added:
+ ----- Method: Player>>getDimensions (in category 'slot-kedama') -----
+ getDimensions
+ 
+ 	^ self getValueFromCostume: #dimensions.
+ !

Item was added:
+ ----- Method: Player>>setDimensions: (in category 'slot-kedama') -----
+ setDimensions: aNumber
+ 
+ 	^ self setCostumeSlot: #dimensions: toValue: aNumber asPoint.
+ !



More information about the Packages mailing list