[Pkg] The Trunk: EToys-fbs.93.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 5 21:53:08 UTC 2013


Frank Shearar uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-fbs.93.mcz

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

Name: EToys-fbs.93
Author: fbs
Time: 5 March 2013, 6:32:45.848 pm
UUID: 669123f2-ac73-4f25-8ef6-8d605db8e074
Ancestors: EToys-fbs.92

Moved Morph's "geometry eToy" and "latter day support" methods  to Etoys.

=============== Diff against EToys-fbs.92 ===============

Item was added:
+ ----- Method: Morph>>addTransparentSpacerOfSize: (in category '*Etoys-geometry') -----
+ addTransparentSpacerOfSize: aPoint
+ 	self addMorphBack: (self transparentSpacerOfSize: aPoint)!

Item was added:
+ ----- Method: Morph>>beTransparent (in category '*Etoys-geometry') -----
+ beTransparent
+ 	self color: Color transparent!

Item was added:
+ ----- Method: Morph>>cartesianBoundsTopLeft (in category '*Etoys-geometry') -----
+ cartesianBoundsTopLeft
+ 	"Answer the origin of this morph relative to it's container's cartesian origin. 
+ 	NOTE: y DECREASES toward the bottom of the screen"
+ 
+ 	| w container |
+ 
+ 	w := self world ifNil: [^ bounds origin].
+ 	container := self referencePlayfield ifNil: [w].
+ 	^ (bounds left - container cartesianOrigin x) @
+ 		(container cartesianOrigin y - bounds top)!

Item was added:
+ ----- Method: Morph>>cartesianXY: (in category '*Etoys-geometry') -----
+ cartesianXY: coords
+ 	^ self x: coords x y: coords y
+ !

Item was added:
+ ----- Method: Morph>>color:sees: (in category '*Etoys-geometry') -----
+ color: sensitiveColor sees: soughtColor 
+ 	"Return true if any of my pixels of sensitiveColor intersect with pixels of soughtColor."
+ 
+ 	"Make a mask with black where sensitiveColor is, white elsewhere"
+ 
+ 	| myImage sensitivePixelMask map patchBelowMe tfm morphAsFlexed i1 pasteUp |
+ 	pasteUp := self world ifNil: [ ^false ].
+ 	tfm := self transformFrom: pasteUp.
+ 	morphAsFlexed := tfm isIdentity 
+ 				ifTrue: [self]
+ 				ifFalse: [TransformationMorph new flexing: self clone byTransformation: tfm].
+ 	myImage := morphAsFlexed imageForm offset: 0 @ 0.
+ 	sensitivePixelMask := Form extent: myImage extent depth: 1.
+ 	"ensure at most a 16-bit map"
+ 	map := Bitmap new: (1 bitShift: (myImage depth - 1 min: 15)).
+ 	map at: (i1 := sensitiveColor indexInMap: map) put: 1.
+ 	sensitivePixelMask 
+ 		copyBits: sensitivePixelMask boundingBox
+ 		from: myImage form
+ 		at: 0 @ 0
+ 		colorMap: map.
+ 
+ 	"get an image of the world below me"
+ 	patchBelowMe := pasteUp 
+ 				patchAt: morphAsFlexed fullBounds
+ 				without: self
+ 				andNothingAbove: false.
+ 	"
+ sensitivePixelMask displayAt: 0 at 0.
+ patchBelowMe displayAt: 100 at 0.
+ "
+ 	"intersect world pixels of the color we're looking for with the sensitive pixels"
+ 	map at: i1 put: 0.	"clear map and reuse it"
+ 	map at: (soughtColor indexInMap: map) put: 1.
+ 	sensitivePixelMask 
+ 		copyBits: patchBelowMe boundingBox
+ 		from: patchBelowMe
+ 		at: 0 @ 0
+ 		clippingBox: patchBelowMe boundingBox
+ 		rule: Form and
+ 		fillColor: nil
+ 		map: map.
+ 	"
+ sensitivePixelMask displayAt: 200 at 0.
+ "
+ 	^(sensitivePixelMask tallyPixelValues second) > 0!

Item was added:
+ ----- Method: Morph>>colorUnder (in category '*Etoys-geometry') -----
+ colorUnder
+ 	"Return the color of under the receiver's center."
+ 
+ 	self isInWorld
+ 		ifTrue: [^ self world colorAt: (self pointInWorld: self referencePosition) belowMorph: self]
+ 		ifFalse: [^ Color black].
+ !

Item was added:
+ ----- Method: Morph>>degreesOfFlex (in category '*Etoys-geometry') -----
+ degreesOfFlex
+ 	"Return any rotation due to flexing"
+ 	"NOTE: because renderedMorph, which is used by the halo to set heading, goes down through dropShadows as well as transformations, we need this method (and its other implems) to come back up through such a chain."
+ 	^ 0.0!

Item was added:
+ ----- Method: Morph>>forwardDirection: (in category '*Etoys-geometry') -----
+ forwardDirection: newDirection
+ 	"Set the receiver's forward direction (in eToy terms)"
+ 	self setProperty: #forwardDirection toValue: newDirection.!

Item was added:
+ ----- Method: Morph>>getIndexInOwner (in category '*Etoys-geometry') -----
+ getIndexInOwner
+ 	"Answer which position the receiver holds in its owner's hierarchy"
+ 
+ 	"NB: There is some concern about submorphs that aren't really to be counted, such as a background morph of a playfield."
+ 
+ 	| container topRenderer |
+ 	container := (topRenderer := self topRendererOrSelf) owner.
+ 	^ container submorphIndexOf: topRenderer.!

Item was added:
+ ----- Method: Morph>>goHome (in category '*Etoys-geometry') -----
+ goHome
+ 	| box fb |
+ 	owner isInMemory ifFalse: [^ self].
+ 	owner isNil ifTrue: [^ self].
+ 	self visible ifFalse: [^ self].
+ 
+ 	box := owner visibleClearArea.
+ 	fb := self fullBounds.
+ 
+ 	fb left < box left
+ 		ifTrue: [self left: box left - fb left + self left].
+ 	fb right > box right
+ 		ifTrue: [self right: box right - fb right + self right].
+ 
+ 	fb top < box top
+ 		ifTrue: [self top: box top - fb top + self top].
+ 	fb bottom > box bottom
+ 		ifTrue: [self bottom: box bottom - fb bottom + self bottom].
+ !

Item was added:
+ ----- Method: Morph>>heading (in category '*Etoys-geometry') -----
+ heading
+ 	"Return the receiver's heading (in eToy terms)"
+ 	owner ifNil: [^ self forwardDirection].
+ 	^ self forwardDirection + owner degreesOfFlex!

Item was added:
+ ----- Method: Morph>>heading: (in category '*Etoys-geometry') -----
+ heading: newHeading
+ 	"Set the receiver's heading (in eToy terms)"
+ 	self isFlexed ifFalse:[self addFlexShell].
+ 	owner rotationDegrees: (newHeading - self forwardDirection).!

Item was added:
+ ----- Method: Morph>>isEtoyReadout (in category '*Etoys-latter day support') -----
+ isEtoyReadout
+ 	"Answer whether the receiver can serve as an etoy readout"
+ 
+ 	^ false!

Item was added:
+ ----- Method: Morph>>move:toPosition: (in category '*Etoys-geometry') -----
+ move: aMorph toPosition: aPointOrNumber
+ 	"Support for e-toy demo. Move the given submorph to the given position. Allows the morph's owner to determine the policy for motion. For example, moving forward through a table might mean motion only in the x-axis with wrapping modulo the table size."
+ 
+ 	aMorph position: aPointOrNumber asPoint.
+ !

Item was added:
+ ----- Method: Morph>>referencePosition (in category '*Etoys-geometry') -----
+ referencePosition
+ 	"Return the current reference position of the receiver"
+ 	| box |
+ 	box := self bounds.
+ 	^box origin + (self rotationCenter * box extent).
+ !

Item was added:
+ ----- Method: Morph>>referencePosition: (in category '*Etoys-geometry') -----
+ referencePosition: aPosition
+ 	"Move the receiver to match its reference position with aPosition"
+ 	| newPos intPos |
+ 	newPos := self position + (aPosition - self referencePosition).
+ 	intPos := newPos asIntegerPoint.
+ 	newPos = intPos 
+ 		ifTrue:[self position: intPos]
+ 		ifFalse:[self position: newPos].!

Item was added:
+ ----- Method: Morph>>referencePositionInWorld (in category '*Etoys-geometry') -----
+ referencePositionInWorld
+ 
+ 	^ self pointInWorld: self referencePosition
+ !

Item was added:
+ ----- Method: Morph>>referencePositionInWorld: (in category '*Etoys-geometry') -----
+ referencePositionInWorld: aPoint
+ 	| localPosition |
+ 	localPosition := owner
+ 		ifNil: [aPoint]
+ 		ifNotNil: [(owner transformFrom: self world) globalPointToLocal: aPoint].
+ 
+ 	self referencePosition: localPosition
+ !

Item was added:
+ ----- Method: Morph>>rotationCenter (in category '*Etoys-geometry') -----
+ rotationCenter
+ 	"Return the rotation center of the receiver. The rotation center defines the relative offset inside the receiver's bounds for locating the reference position."
+ 	^self valueOfProperty: #rotationCenter ifAbsent:[0.5 at 0.5]
+ !

Item was added:
+ ----- Method: Morph>>rotationCenter: (in category '*Etoys-geometry') -----
+ rotationCenter: aPointOrNil
+ 	"Set the new rotation center of the receiver. The rotation center defines the relative offset inside the receiver's bounds for locating the reference position."
+ 	aPointOrNil isNil
+ 		ifTrue:[self removeProperty: #rotationCenter]
+ 		ifFalse:[self setProperty: #rotationCenter toValue: aPointOrNil]
+ !

Item was added:
+ ----- Method: Morph>>scale: (in category '*Etoys-geometry') -----
+ scale: newScale
+ 	"Backstop for morphs that don't have to do something special to set their scale"
+ !

Item was added:
+ ----- Method: Morph>>scaleFactor: (in category '*Etoys-geometry') -----
+ scaleFactor: newScale 
+ 	"Backstop for morphs that don't have to do something special to set their 
+ 	scale "
+ 	| toBeScaled |
+ 	toBeScaled := self.
+ 	newScale = 1.0
+ 		ifTrue: [(self heading isZero
+ 					and: [self isFlexMorph])
+ 				ifTrue: [toBeScaled := self removeFlexShell]]
+ 		ifFalse: [self isFlexMorph
+ 				ifFalse: [toBeScaled := self addFlexShellIfNecessary]].
+ 
+ 	toBeScaled scale: newScale.
+ 
+ 	toBeScaled == self ifTrue: [
+ 		newScale = 1.0
+ 			ifTrue: [ self removeProperty: #scaleFactor ]
+ 			ifFalse: [ self setProperty: #scaleFactor toValue: newScale ]]!

Item was added:
+ ----- Method: Morph>>setDirectionFrom: (in category '*Etoys-geometry') -----
+ setDirectionFrom: aPoint
+ 	| delta degrees |
+ 	delta := (self transformFromWorld globalPointToLocal: aPoint) - self referencePosition.
+ 	degrees := delta degrees + 90.0.
+ 	self forwardDirection: (degrees \\ 360) rounded.
+ !

Item was added:
+ ----- Method: Morph>>setIndexInOwner: (in category '*Etoys-geometry') -----
+ setIndexInOwner: anInteger
+ 	"Answer which position the receiver holds in its owner's hierarchy"
+ 
+ 	"There is some concern about submorphs that aren't really to be counted, such as a background morph of a playfield."
+ 	| container topRenderer indexToUse |
+ 	container := (topRenderer := self topRendererOrSelf) owner.
+ 	indexToUse := (anInteger min: container submorphCount) max: 1.
+ 	container addMorph: topRenderer asElementNumber: indexToUse!

Item was added:
+ ----- Method: Morph>>simplySetVisible: (in category '*Etoys-geometry') -----
+ simplySetVisible: aBoolean
+ 	"Set the receiver's visibility property.  This mild circumlocution is because my TransfomationMorph #visible: method would also set the visibility flag of my flexee, which in this case is pointless because it's the flexee that calls this.
+ 	This appears in morph as a backstop for morphs that don't inherit from TFMorph"
+ 
+ 	self visible: aBoolean!

Item was added:
+ ----- Method: Morph>>touchesColor: (in category '*Etoys-geometry') -----
+ touchesColor: soughtColor 
+ 	"Return true if any of my pixels overlap pixels of soughtColor."
+ 
+ 	"Make a shadow mask with black in my shape, white elsewhere"
+ 
+ 	| map patchBelowMe shadowForm tfm morphAsFlexed pasteUp |
+ 	pasteUp := self world ifNil: [ ^false ].
+ 
+ 	tfm := self transformFrom: pasteUp.
+ 	morphAsFlexed := tfm isIdentity 
+ 				ifTrue: [self]
+ 				ifFalse: [TransformationMorph new flexing: self clone byTransformation: tfm].
+ 	shadowForm := morphAsFlexed shadowForm offset: 0 @ 0.
+ 
+ 	"get an image of the world below me"
+ 	patchBelowMe := (pasteUp 
+ 				patchAt: morphAsFlexed fullBounds
+ 				without: self
+ 				andNothingAbove: false) offset: 0 @ 0.
+ 	"
+ shadowForm displayAt: 0 at 0.
+ patchBelowMe displayAt: 100 at 0.
+ "
+ 	"intersect world pixels of the color we're looking for with our shape."
+ 	"ensure a maximum 16-bit map"
+ 	map := Bitmap new: (1 bitShift: (patchBelowMe depth - 1 min: 15)).
+ 	map at: (soughtColor indexInMap: map) put: 1.
+ 	shadowForm 
+ 		copyBits: patchBelowMe boundingBox
+ 		from: patchBelowMe
+ 		at: 0 @ 0
+ 		clippingBox: patchBelowMe boundingBox
+ 		rule: Form and
+ 		fillColor: nil
+ 		map: map.
+ 	"
+ shadowForm displayAt: 200 at 0.
+ "
+ 	^(shadowForm tallyPixelValues second) > 0!

Item was added:
+ ----- Method: Morph>>transparentSpacerOfSize: (in category '*Etoys-geometry') -----
+ transparentSpacerOfSize: aPoint
+ 	^ (Morph new extent: aPoint) color: Color transparent!

Item was added:
+ ----- Method: Morph>>wrap (in category '*Etoys-geometry') -----
+ wrap
+ 
+ 	| myBox box newX newY wrapped |
+ 	owner ifNil: [^ self].
+ 	myBox := self fullBounds.
+ 	myBox corner < (50000 at 50000) ifFalse: [
+ 		self inform: 'Who is trying to wrap a hidden object?'. ^ self].
+ 	box := owner bounds.
+ 	newX := self position x.
+ 	newY := self position y.
+ 	wrapped := false.
+ 	((myBox right < box left) or: [myBox left > box right]) ifTrue: [
+ 		newX := box left + ((self position x - box left) \\ box width).
+ 		wrapped := true].
+ 	((myBox bottom < box top) or: [myBox top > box bottom]) ifTrue: [
+ 		newY := box top + ((self position y - box top) \\ box height).
+ 		wrapped := true].
+ 	self position: newX at newY.
+ 	(wrapped and: [owner isPlayfieldLike])
+ 		ifTrue: [owner changed].  "redraw all turtle trails if wrapped"
+ 
+ !

Item was added:
+ ----- Method: Morph>>x (in category '*Etoys-geometry') -----
+ x
+ 	"Return my horizontal position relative to the cartesian origin of a relevant playfield"
+ 
+ 	| aPlayfield |
+ 	aPlayfield := self referencePlayfield.
+ 	^aPlayfield isNil 
+ 		ifTrue: [self referencePosition x]
+ 		ifFalse: [self referencePosition x - aPlayfield cartesianOrigin x]!

Item was added:
+ ----- Method: Morph>>x: (in category '*Etoys-geometry') -----
+ x: aNumber 
+ 	"Set my horizontal position relative to the cartesian origin of the playfield or the world."
+ 
+ 	| offset aPlayfield newX |
+ 	aPlayfield := self referencePlayfield.
+ 	offset := self left - self referencePosition x.
+ 	newX := aPlayfield isNil
+ 				ifTrue: [aNumber + offset]
+ 				ifFalse: [aPlayfield cartesianOrigin x + aNumber + offset].
+ 	self position: newX @ bounds top!

Item was added:
+ ----- Method: Morph>>x:y: (in category '*Etoys-geometry') -----
+ x: xCoord y: yCoord
+ 	| aWorld xyOffset delta aPlayfield |
+ 	(aWorld := self world) ifNil: [^ self position: xCoord @ yCoord].
+ 	xyOffset := self topLeft - self referencePosition.
+ 	delta := (aPlayfield := self referencePlayfield)
+ 		ifNil:
+ 			[xCoord @ (aWorld bottom - yCoord)]
+ 		ifNotNil:
+ 			[aPlayfield cartesianOrigin + (xCoord @ (yCoord negated))].
+ 	self position: (xyOffset + delta)
+ !

Item was added:
+ ----- Method: Morph>>y (in category '*Etoys-geometry') -----
+ y
+ 	"Return my vertical position relative to the cartesian origin of the playfield or the world. Note that larger y values are closer to the top of the screen."
+ 
+ 	| w aPlayfield |
+ 	w := self world.
+ 	w ifNil: [^bounds top].
+ 	aPlayfield := self referencePlayfield.
+ 	^aPlayfield isNil 
+ 		ifTrue: [w cartesianOrigin y - self referencePosition y]
+ 		ifFalse: [aPlayfield cartesianOrigin y - self referencePosition y]!

Item was added:
+ ----- Method: Morph>>y: (in category '*Etoys-geometry') -----
+ y: aNumber 
+ 	"Set my vertical position relative to the cartesian origin of the playfield or the world. Note that larger y values are closer to the top of the screen."
+ 
+ 	| w offset newY aPlayfield |
+ 	w := self world.
+ 	w ifNil: [^self position: bounds left @ aNumber].
+ 	aPlayfield := self referencePlayfield.
+ 	offset := self top - self referencePosition y.
+ 	newY := aPlayfield isNil
+ 				ifTrue: [w bottom - aNumber + offset]
+ 				ifFalse: [aPlayfield cartesianOrigin y - aNumber + offset].
+ 	self position: bounds left @ newY!



More information about the Packages mailing list