Graphics With Squeak ... ;)

Ali Chamas ali at sparkdigital.com.au
Wed Apr 18 00:00:00 UTC 2001


> From: Karl Ramberg <karl.ramberg at chello.se>
> Reply-To: "squeak at cs.uiuc.edu" <squeak at cs.uiuc.edu>
> Date: Tue, 17 Apr 2001 19:45:19 +0200
> To: squeak at cs.uiuc.edu
> Subject: Re: Graphics With Squeak ... ;)
> Resent-From: squeak at cs.uiuc.edu
> Resent-Date: 17 Apr 2001 17:45:09 -0000
> 
> Nice stuff
> I have agree with Henrik, code + examples in a change set/ image segment
> would be fun.
> 
> Karl
> 

Here they are, happy Squeaking.

The classes (Polygon1 - 4) have a run method. A few of them just need a
rectangle selected, others need you to keep clicking (creating) polygon
edges until a "shit-click" happens. I stayed up late when i was working on
finishing these images, and i used a lot of "magic" numbers and workspace
tweaking, so you might find some new patterns and results.

Thanks for the great feedback. BTW, i'm working on my second revision of a
2D game engine i've working on in Squeak for about a year now. I can't wait
to finish it because then i will be making some amazing games with Squeak.
Stay tuned! The truth is Smalltalk...

Ali.

-------------- next part --------------
Object subclass: #Polygon
	instanceVariableNames: 'animate iterator maxIterations points alpha borderColor fillColor borderWidth shapeDistorter transformMatrix subdivide spawnLevel rotation xscale yscale translation center '
	classVariableNames: 'SpawnMax '
	poolDictionaries: ''
	category: 'Assignment1'!
!Polygon commentStamp: 'Ali Chamas 4/12/2001 12:38' prior: 0!
I represent a collection of RowVectors (points) which connect to form a 2D polygon in world space.
I support matrix transformation of my points by holding my private values for translation, scaling, and rotation.
I can combine matricies or apply the single matricies through commands.
I am always closed, and have a borderWidth / borderColor / fillColor / alpha value for appearance.
I support animation iteration which will enable me to enter an animation loop of 'x' iterations.
For each iteration, i receive the message #iterator: and #step.!


!Polygon methodsFor: 'initialise'!
initialise
	"this should be subclassed so that a polygon subclass can prepare any specific values..."
	^ self! !


!Polygon methodsFor: 'accessing' stamp: 'Ali Chamas 4/10/2001 09:55'!
alpha
	alpha isNil ifTrue: [alpha _ 1.0].
	^ alpha! !

!Polygon methodsFor: 'accessing' stamp: 'Ali Chamas 4/11/2001 18:33'!
amountDone
^ (self iterator / self maxIterations) asFloat! !

!Polygon methodsFor: 'accessing' stamp: 'Ali Chamas 4/11/2001 18:34'!
amountDoneReveresed
	^ 1.0 - ((self iterator / self maxIterations) asFloat)! !

!Polygon methodsFor: 'accessing' stamp: 'Ali Chamas 4/5/2001 21:53'!
basicPoints
^ self points collect: [ :rowVector | rowVector x @ rowVector y ]! !

!Polygon methodsFor: 'accessing'!
borderColor
	borderColor isNil ifTrue: [borderColor _ self fillColor].
	^ borderColor alpha: self alpha! !

!Polygon methodsFor: 'accessing'!
borderWidth
	borderWidth isNil ifTrue: [borderWidth _ 1].
	^ borderWidth! !

!Polygon methodsFor: 'accessing'!
bounds
	| xsort ysort |
	xsort _ SortedCollection sortBlock: [:a :b | a x < b x].
	xsort addAll: self points.
	ysort _ SortedCollection sortBlock: [:a :b | a y < b y].
	ysort addAll: self points.
	^ xsort first x asInteger @ ysort first y asInteger rect: xsort last x asInteger @ ysort last y asInteger! !

!Polygon methodsFor: 'accessing'!
center
	center isNil ifTrue: [^ self bounds center].
^ center! !

!Polygon methodsFor: 'accessing'!
fillColor
	fillColor isNil ifTrue: [fillColor _ Color white].
	^ fillColor alpha: self alpha! !

!Polygon methodsFor: 'accessing'!
iterator
	iterator isNil ifTrue: [iterator _ 1].
	^ iterator! !

!Polygon methodsFor: 'accessing'!
maxIterations
	maxIterations isNil ifTrue: [maxIterations _ 50].
	^ maxIterations! !

!Polygon methodsFor: 'accessing'!
points
	points isNil ifTrue: [points _ OrderedCollection new].
	^ points! !

!Polygon methodsFor: 'accessing'!
rotation
	rotation isNil ifTrue: [rotation _ 0].
	^ rotation! !

!Polygon methodsFor: 'accessing' stamp: 'Ali Chamas 4/5/2001 21:26'!
shapeDistorter

shapeDistorter isNil ifTrue: [shapeDistorter := nil].

^ shapeDistorter! !

!Polygon methodsFor: 'accessing'!
spawnLevel
	spawnLevel isNil ifTrue: [spawnLevel _ 1].
	^ spawnLevel! !

!Polygon methodsFor: 'accessing'!
subdivide
	subdivide isNil ifTrue: [subdivide _ false].
	^ subdivide! !

!Polygon methodsFor: 'accessing'!
transformMatrix
	transformMatrix isNil ifTrue: [transformMatrix _ TransformMatrix new].
	^ transformMatrix! !

!Polygon methodsFor: 'accessing'!
translation
	translation isNil ifTrue: [translation _ 0 at 0].
	^ translation! !

!Polygon methodsFor: 'accessing'!
xscale
	xscale isNil ifTrue: [xscale _ 1.0].
	^ xscale! !

!Polygon methodsFor: 'accessing'!
yscale
	yscale isNil ifTrue: [yscale _ 1.0].
	^ yscale! !


!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/10/2001 09:56'!
alpha: value 
	alpha _ value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:09'!
animate: value

animate := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
borderColor: value

borderColor := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
borderWidth: value

borderWidth := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:12'!
center: value

center := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
fillColor: value

fillColor := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
iterator: value

iterator := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:27'!
maxIterations: value

maxIterations := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
points: value

points := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 18:51'!
rect: value

rect := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:09'!
rotation: value

rotation := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:19'!
scale: amount
xscale := amount. yscale := amount! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
shapeDistorter: value

shapeDistorter := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 19:30'!
spawnLevel: level
spawnLevel := level! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:30'!
subdivide: value

subdivide := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/5/2001 21:26'!
transformMatrix: value

transformMatrix := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:09'!
translation: value

translation := value! !

!Polygon methodsFor: 'updating'!
translationFromRadius: r degrees: theta 
	self translation: (Point r: r degrees: theta)! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:09'!
xscale: value

xscale := value! !

!Polygon methodsFor: 'updating' stamp: 'Ali Chamas 4/9/2001 20:09'!
yscale: value

yscale := value! !


!Polygon methodsFor: 'transforming'!
distortSelf
"apply the shape distorter to my points..."
	self shapeDistorter distort: self! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 20:18'!
moveBy: delta
	self transformMatrix: (TranslationMatrix deltaX: delta x deltaY: delta y).
	self transform! !

!Polygon methodsFor: 'transforming'!
moveTo: point 
	self moveTo: point offset: 0 @ 0!
]style[(8 5 3 4 9 5 9 1 3 1)f1b,f1cmagenta;ib,f1,f1cblue;b,f1,f1cmagenta;b,f1,f1c152050000,f1,f1c152050000! !

!Polygon methodsFor: 'transforming'!
moveTo: point offset: offset 
	self transformMatrix: (TranslationMatrix deltaX: self center x negated deltaY: self center y negated)
			* (TranslationMatrix deltaX: point x + offset x deltaY: point y + offset y).
	self transform! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 19:56'!
rotateBy: degrees
self rotateBy: degrees about: self center! !

!Polygon methodsFor: 'transforming'!
rotateBy: degrees about: c 
	self transformMatrix: (TranslationMatrix deltaX: c x negated deltaY: c y negated)
			* (RotationMatrix degrees: degrees) * (TranslationMatrix deltaX: c x deltaY: c y).
	self transform! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 19:57'!
scaleBy: amount 
	self scaleBy: amount about: self center! !

!Polygon methodsFor: 'transforming'!
scaleBy: amount about: c 
	self transformMatrix: (TranslationMatrix deltaX: c x negated deltaY: c y negated)
			* (ScalingMatrix scale: amount) * (TranslationMatrix deltaX: c x deltaY: c y).
	self transform! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 20:17'!
scaleXBy: amount
self scaleXBy: amount about: self center! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 20:15'!
scaleXBy: amount about: c 
	self transformMatrix: (TranslationMatrix deltaX: c x negated deltaY: c y negated)
			* (ScalingMatrix xscale: amount yscale: 1.0) * (TranslationMatrix deltaX: c x deltaY: c y).
	self transform! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 20:17'!
scaleYBy: amount 
	self scaleYBy: amount about: self center! !

!Polygon methodsFor: 'transforming' stamp: 'Ali Chamas 4/9/2001 20:15'!
scaleYBy: amount about: c 
	self transformMatrix: (TranslationMatrix deltaX: c x negated deltaY: c y negated)
			* (ScalingMatrix xscale: 1.0 yscale: amount) * (TranslationMatrix deltaX: c x deltaY: c y).
	self transform! !

!Polygon methodsFor: 'transforming'!
subdivideSelf
"double the amount of points which make up edges by taking every line segment i have and adding a midpoint between the point indexes..."
	| basicPoints newPoints |
	newPoints _ OrderedCollection new.
	basicPoints _ self basicPoints copy.
	basicPoints add: (basicPoints at: 1).
	1 to: basicPoints size - 1 do: 
		[:i | 
		| point midPoint nextPoint | 
		point _ basicPoints at: i.
		nextPoint _ basicPoints at: i + 1.
		midPoint _ point interpolateTo: nextPoint at: 0.5.
		newPoints add: point;
		 add: midPoint].
	self points: (newPoints collect: [:point | RowVector fromPoint: point])! !

!Polygon methodsFor: 'transforming'!
transform
	"this multiplies each one of my points (RowVector's) by my  
	transformMatrix instance variable..."
	self points: (self points collect: [:point | point * self transformMatrix])! !


!Polygon methodsFor: 'spawning'!
spawn
"create a new me with some of my basic properties..."
	| new |
	self spawnLevel > SpawnMax
		ifTrue: 
			[animate _ false.
			^ nil].
	new _ self class new.
	new points: (self points collect: [:point | point deepCopy]).
	new spawnLevel: self spawnLevel + 1.
	^ new! !


!Polygon methodsFor: 'display/animation'!
animate
	"this enters the polygons into it's drawing loop..."
	animate _ true.
	1 to: self maxIterations do: 
		[:i | 
		self iterator: i.
		self step].! !

!Polygon methodsFor: 'display/animation'!
debugDraw
	"this will draw all of the points, a green point for the first vertex, and a red center point for the bounding boxes center. The bounding box will also be drawn..."
	| p |
	p _ Pen newOnForm: Display.
	p roundNib: 3.
	self draw.
	Display
		border: self bounds
		width: 1
		fillColor: Color red.
	p color: Color blue.
	self basicPoints do: [:point | p place: point;
		 goto: point].
	p color: Color green;
	 roundNib: 5;
	 place: self basicPoints first;
	 goto: self basicPoints first.
	p color: Color red;
	 place: self center;
	 goto: self center! !

!Polygon methodsFor: 'display/animation'!
draw
	"this renders me cleanly to the screen..."
	| canvas |
	canvas _ FormCanvas on: Display.
	canvas
		drawPolygon: self basicPoints asArray
		fillStyle: self fillColor
		borderWidth: self borderWidth
		borderColor: self borderColor! !

!Polygon methodsFor: 'display/animation'!
step
	"this draws a single iteration..."
	animate ifFalse: [^ nil].
	self subdivide ifTrue: [self subdivideSelf].
	self shapeDistorter isNil ifFalse: [self distortSelf].
	self moveBy: self translation.
	self scaleXBy: self xscale.
	self scaleYBy: self yscale.
	self rotateBy: self rotation.
	self draw! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Polygon class
	instanceVariableNames: ''!

!Polygon class methodsFor: 'instance creation'!
circleWithRadius: radius steps: steps firstDegree: firstDegree 
	| points |
	points _ OrderedCollection new.
	1 to: steps asInteger do: [:i |  points add: (RowVector fromPoint: (Point r: radius degrees: 360 * (i / steps) - firstDegree))].
	^ points! !

!Polygon class methodsFor: 'instance creation' stamp: 'Ali Chamas 4/10/2001 19:27'!
fromPoints: points
|n|
n := self new.
n points: points.
^ n! !

!Polygon class methodsFor: 'instance creation'!
fromRectangle: rect 
	| n |
	n _ self new.
	n points add: (RowVector fromPoint: rect topLeft);
	 add: (RowVector fromPoint: rect topRight);
	 add: (RowVector fromPoint: rect bottomRight);
	 add: (RowVector fromPoint: rect bottomLeft).
	^ n! !

!Polygon class methodsFor: 'instance creation'!
fromUser
	| new |
	new _ self new.
	[Sensor shiftPressed]
		whileFalse: [new points add: (RowVector fromPoint: Point fromUser)].
	^ new! !

!Polygon class methodsFor: 'instance creation'!
pointsFromUser
	| collection |
	collection _ OrderedCollection new.
	[Sensor shiftPressed]
		whileFalse: [collection add: (RowVector fromPoint: Point fromUser)].
	^ collection! !


!Polygon class methodsFor: 'spawning' stamp: 'Ali Chamas 4/9/2001 19:54'!
spawnMax 
	^ SpawnMax! !

!Polygon class methodsFor: 'spawning' stamp: 'Ali Chamas 4/9/2001 19:31'!
spawnMax: value
SpawnMax := value! !


!Polygon class methodsFor: 'documentation'!
testSubdivideAndDistort
	| p |
	p _ Polygon fromUser.
	p shapeDistorter: (RandomDistorter xamount: 2 yamount: 20).
	1 to: 5 do: [:i | p debugDraw; moveBy: 100 @ 0; subdivideSelf; distortSelf]! !


Polygon subclass: #Polygon1
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!

!Polygon1 methodsFor: 'animation'!
initialise
	self scale: 0.99;
	 fillColor: Color blue! !

!Polygon1 methodsFor: 'animation'!
iterator: value 
	super iterator: value.
	value = 5
		ifTrue: 
			[| n | 
			n _ self spawn.
			n isNil ifTrue: [^ nil].
			n rotation: (self rotation + 45) asInteger;
			 fillColor: (Color
					r: self fillColor red + 0.03
					g: self fillColor green
					b: self fillColor blue);
			 animate]! !

!Polygon1 methodsFor: 'animation'!
step
	self fillColor: self fillColor;
	 alpha: self alpha - 0.05;
	 rotation: self rotation + 20.
	super step! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Polygon1 class
	instanceVariableNames: ''!

!Polygon1 class methodsFor: 'documentation'!
run
	| p pnts |
	pnts _ Polygon pointsFromUser.
	1 to: 15 do: 
		[:i | 
		p _ Polygon1 fromPoints: pnts.
		p initialise.
		p rotation: i * 45;
		 fillColor: (Color
				r: i / 30
				g: 0
				b: i / 15);
		 translationFromRadius: 1 degrees: i * 45.
		p animate]! !


Polygon subclass: #Polygon2
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!

!Polygon2 methodsFor: 'initialise'!
initialise
	self scale: 0.9;
	 rotation: 2;
	 maxIterations: 20;
	 fillColor: Color red twiceDarker;
	 shapeDistorter: (WaveDistorter xamount: 5 yamount: 5)! !


!Polygon2 methodsFor: 'animation'!
iterator: i 
	self alpha: ((i*12)/256) asFloat.
	super iterator: i! !

!Polygon2 methodsFor: 'animation'!
step
	self fillColor: self fillColor slightlyLighter;
	 borderColor: self fillColor lighter;
	 subdivideSelf;
	 distortSelf.
	super step! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Polygon2 class
	instanceVariableNames: ''!

!Polygon2 class methodsFor: 'documentation'!
run
	| p |
	p _ Polygon2 fromRectangle: Rectangle fromUser.
	p initialise.
	p animate! !


Polygon subclass: #Polygon3
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!

!Polygon3 methodsFor: 'animation' stamp: 'Ali Chamas 4/11/2001 11:30'!
degrees: d
degrees := d! !

!Polygon3 methodsFor: 'animation'!
initialise
	self scale: 0.997;
	 maxIterations: 600;
	 shapeDistorter: (WaveDistorter yamount: 2)! !

!Polygon3 methodsFor: 'animation'!
iterator: i 
	self alpha: 0.5 - (i / self maxIterations) asFloat.
	super iterator: i! !

!Polygon3 methodsFor: 'animation'!
step
	self fillColor: (self fillColor mixed: 1.0 - (self iterator / self maxIterations) asFloat * 1.0 with: Color blue) lighter;
	 borderColor: self fillColor darker.
	self translationFromRadius: 10 degrees: self rotation;
	 rotation: self rotation + 5.
	super step! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Polygon3 class
	instanceVariableNames: ''!

!Polygon3 class methodsFor: 'documentation'!
run
	| p ps c |
	ps _ Polygon pointsFromUser.
	1 to: 40 do: 
		[:i | 
		c _ Color
					r: 0
					g: 0
					b: (i * 5 / 256) asFloat.
		p _ Polygon3 new.
		p points: ps;
		 fillColor: c;
		 initialise.
		p animate]! !


Polygon subclass: #Polygon4
	instanceVariableNames: 'r red '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!

!Polygon4 methodsFor: 'animation'!
initialise
	r _ 200.
	self points: (Polygon
			circleWithRadius: 100
			steps: 20
			firstDegree: 0);
	 moveTo: self location;
	 maxIterations: 400;
	 subdivide: false;
	 alpha: 0.0;
	 fillColor: nil! !

!Polygon4 methodsFor: 'animation'!
location
	^ (Point r: r degrees: self rotation)
		+ Display center! !

!Polygon4 methodsFor: 'animation' stamp: 'Ali Chamas 4/11/2001 19:19'!
red: value
red := value! !

!Polygon4 methodsFor: 'animation'!
step
	super step.
	self alpha: self amountDone * 0.5;
	 fillColor: (Color
			r: self amountDone
			g: red
			b: self amountDoneReveresed);
	 borderColor: self fillColor twiceLighter.
	self moveTo: self location.
	self rotation: self rotation + 1.
	(r _ r - 1) < 1 ifTrue: [r _ 1]! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Polygon4 class
	instanceVariableNames: ''!

!Polygon4 class methodsFor: 'documentation'!
run
	| p |
	1 to: 10 do: 
		[:i | 
		p _ self new.
		p initialise; yscale: 0.98; red: i / 10; shapeDistorter: (WaveDistorter xamount: 2 yamount: 0); rotation: i * (360 / 10); animate]! !


Object subclass: #RowVector
	instanceVariableNames: 'x y z '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!RowVector commentStamp: 'Ali Chamas 4/12/2001 12:43' prior: 0!
I represent a point in homogenous space in the form of a simple 3x1 row vector matrix.
My elements consist of x, y, and a constant w (1).
I can be multiplied by a square tranformation matrix.!


!RowVector methodsFor: 'accessing'!
x
	x isNil ifTrue: [x _ 0].
	^ x! !

!RowVector methodsFor: 'accessing'!
y
	y isNil ifTrue: [y _ 0].
	^ y! !

!RowVector methodsFor: 'accessing'!
z
	z isNil ifTrue: [z _ 1].
	^ z! !


!RowVector methodsFor: 'updating' stamp: 'Ali Chamas 4/4/2001 17:50'!
x: value

x := value! !

!RowVector methodsFor: 'updating' stamp: 'Ali Chamas 4/4/2001 17:50'!
y: value

y := value! !

!RowVector methodsFor: 'updating' stamp: 'Ali Chamas 4/4/2001 18:49'!
z: value

z := value! !


!RowVector methodsFor: 'matrix algebra'!
* squareMatrix 
	"return the result of multiplying me with the given 3x3 square matrix..."
	| newMatrix a b |
	"create shortened notation here..."
	a _ self.
	b _ squareMatrix.
	"create a new row vector matrix..."
		newMatrix _ self class new.
	"multiple the elements..."
	newMatrix x: a x * b a11 + (a y * b a21) + (a z * b a31).
	newMatrix y: a x * b a12 + (a y * b a22) + (a z * b a32).
	newMatrix z: a x * b a13 + (a y * b a23) + (a z * b a33).
	"return the new matrix..."
	^ newMatrix! !


!RowVector methodsFor: 'printing'!
asString
	^ self x asString , ' ' , self y asString , ' ' , self z asString! !

!RowVector methodsFor: 'printing'!
printOn: aStream 
	"The receiver prints on aStream in terms of a fixed notation."
	self x printOn: aStream.
	aStream nextPut: $#.
	self y printOn: aStream! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

RowVector class
	instanceVariableNames: ''!

!RowVector class methodsFor: 'instance creation'!
fromPoint: point 
	"create a new instance from the given point..."
	^ self x: point x y: point y! !

!RowVector class methodsFor: 'instance creation'!
x: x y: y 
	"create a new instance and initialise it with the given x and y..."
	| new |
	new _ self new.
	new x: x;
	 y: y.
	^ new! !


Object subclass: #ShapeDistorter
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!ShapeDistorter commentStamp: 'Ali Chamas 4/12/2001 12:50' prior: 0!
I am an abstract class representing a shape distortion of a given polygon.
Since most distortion algorithms work with multiple values simultaniously, i
cannot be represented as a matrix (unfortunately). This is because when multiplying
a RowVector by a square matrix, the square matrix does not know about the total set 
of values held by the RowVector, and cannot solve any values simultationously.

This is why i am encapsulated as an object, and attatched to a polygon. When the polygon
is animating, if there is a shapeDistorter object present, it will pass itself to that object, and
it's points will be changed.!


!ShapeDistorter methodsFor: 'distorting'!
distort: polygon 
	self subclassResponsibility! !


Object subclass: #TransformMatrix
	instanceVariableNames: 'a11 a12 a13 a21 a22 a23 a31 a32 a33 '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!TransformMatrix commentStamp: 'Ali Chamas 4/4/2001 18:03' prior: 0!
I represent a simple 3x3 square transformation matrix.
I may be multiplied with other square matricies to form a combined matrix.

My elements are accessed and updated by using the syntax - 

a(i)(j)

where i = the row, and j = the column.

eg. self a12: 1

...will update the second column of the first row with the value 1.!


!TransformMatrix methodsFor: 'elements - accessing'!
a11
	"return the value of the first row, first column..."
	a11 isNil ifTrue: [a11 _ 1].
	^ a11! !

!TransformMatrix methodsFor: 'elements - accessing'!
a12
	"return the value of the first row, second column..."
	a12 isNil ifTrue: [a12 _ 0].
	^ a12! !

!TransformMatrix methodsFor: 'elements - accessing'!
a13
	"return the value of the first row, third column..."
	a13 isNil ifTrue: [a13 _ 0].
	^ a13! !

!TransformMatrix methodsFor: 'elements - accessing'!
a21
	"return the value of the second row, first column..."
	a21 isNil ifTrue: [a21 _ 0].
	^ a21! !

!TransformMatrix methodsFor: 'elements - accessing'!
a22
	"return the value of the second row, second column..."
	a22 isNil ifTrue: [a22 _ 1].
	^ a22! !

!TransformMatrix methodsFor: 'elements - accessing'!
a23
	"return the value of the second row, third column..."
	a23 isNil ifTrue: [a23 _ 0].
	^ a23! !

!TransformMatrix methodsFor: 'elements - accessing'!
a31
	"return the value of the third row, first column..."
	a31 isNil ifTrue: [a31 _ 0].
	^ a31! !

!TransformMatrix methodsFor: 'elements - accessing'!
a32
	"return the value of the third row, second column..."
	a32 isNil ifTrue: [a32 _ 0].
	^ a32! !

!TransformMatrix methodsFor: 'elements - accessing'!
a33
	"return the value of the third row, third column..."
	a33 isNil ifTrue: [a33 _ 1].
	^ a33! !


!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a11: value

a11 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a12: value

a12 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a13: value

a13 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a21: value

a21 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a22: value

a22 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a23: value

a23 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a31: value

a31 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a32: value

a32 := value! !

!TransformMatrix methodsFor: 'elements - updating' stamp: 'Ali Chamas 4/4/2001 17:47'!
a33: value

a33 := value! !


!TransformMatrix methodsFor: 'matrix algebra'!
* squareMatrix 
	"return the result of multiplying me with the given 3x3 square matrix..."
	"create shortened notation here..."
	| newMatrix a b |
	a _ self.
	b _ squareMatrix.
	"create a new square matrix..."
	newMatrix _ self class new.
	"multiply the elements..."
	newMatrix a11: a a11 * b a11 + (a a12 * b a21) + (a a13 * b a31).
	newMatrix a12: a a11 * b a12 + (a a12 * b a22) + (a a13 * b a32).
	newMatrix a13: a a11 * b a13 + (a a12 * b a23) + (a a13 * b a33).
	newMatrix a21: a a21 * b a11 + (a a22 * b a21) + (a a23 * b a31).
	newMatrix a22: a a21 * b a12 + (a a22 * b a22) + (a a23 * b a32).
	newMatrix a23: a a21 * b a13 + (a a22 * b a23) + (a a23 * b a33).
	newMatrix a31: a a31 * b a11 + (a a32 * b a21) + (a a33 * b a31).
	newMatrix a32: a a31 * b a12 + (a a32 * b a22) + (a a33 * b a32).
	newMatrix a33: a a31 * b a13 + (a a32 * b a23) + (a a33 * b a33).
	"return the new matrix..."
	^ newMatrix! !


!TransformMatrix methodsFor: 'printing'!
asString
	"return this 3x3 Matrix as a string..."
	| spc cr |
	spc _ ' '.
	cr _ Character cr asString.
	^ cr , a11 asString , spc , a12 asString , spc , a13 asString , cr ,  a21 asString , spc , a22 asString , spc ,  a23 asString , cr ,  a31 asString , spc ,  a32 asString , spc ,  a33 asString , cr! !

!TransformMatrix methodsFor: 'printing' stamp: 'Ali Chamas 4/4/2001 19:11'!
printString
^ self asString! !


TransformMatrix subclass: #RotationMatrix
	instanceVariableNames: 'theta '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!RotationMatrix commentStamp: 'Ali Chamas 4/4/2001 19:31' prior: 0!
I represent a rotation transformation matrix.
I use a single theta value to represent the amount of rotation.!


!RotationMatrix methodsFor: 'accessing - theta'!
theta
	theta isNil ifTrue: [theta _ 0].
	^ theta! !


!RotationMatrix methodsFor: 'updating - theta'!
theta: value 
	theta _ value.
	"update the appropriate elements values as well..."
	self a11: theta cos.
	self a12: theta sin.
	self a21: theta sin negated.
	self a22: theta cos! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

RotationMatrix class
	instanceVariableNames: ''!

!RotationMatrix class methodsFor: 'instance creation' stamp: 'Ali Chamas 4/9/2001 19:19'!
degrees: degrees
^ self theta: degrees degreesToRadians! !

!RotationMatrix class methodsFor: 'instance creation'!
theta: theta 
	"create a new instance and initialise it's theta from the given value..."
	| new |
	new _ self new.
	new theta: theta.
	^ new! !


TransformMatrix subclass: #ScalingMatrix
	instanceVariableNames: 'xscale yscale '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!ScalingMatrix commentStamp: 'Ali Chamas 4/4/2001 19:31' prior: 0!
I represent a scaling transformation matrix.
I use two scale factors, one for the x axis, and one for the y.!


!ScalingMatrix methodsFor: 'accessing - scale'!
xscale
	xscale isNil ifTrue: [xscale _ 1.0].
	^ xscale! !

!ScalingMatrix methodsFor: 'accessing - scale'!
yscale
	yscale isNil ifTrue: [yscale _ 1.0].
	^ yscale! !


!ScalingMatrix methodsFor: 'updating - scale'!
xscale: value 
	xscale _ value.
	"update the appropriate elements values as well..."
	self a11: xscale! !

!ScalingMatrix methodsFor: 'updating - scale'!
yscale: value 
	yscale _ value.
	"update the appropriate elements values as well..."
	self a22: yscale! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

ScalingMatrix class
	instanceVariableNames: ''!

!ScalingMatrix class methodsFor: 'instance creation'!
scale: scale 
"create a new instance from the given scale value for both X and Y scale factors..."
	^ self xscale: scale yscale: scale! !

!ScalingMatrix class methodsFor: 'instance creation'!
xscale: xscale yscale: yscale 
	"create a new instance and initialise it's X & Y scale factors from the given values..."
	| new |
	new _ self new.
	new xscale: xscale;
	 yscale: yscale.
	^ new! !


TransformMatrix subclass: #ThreeDMatrix
	instanceVariableNames: 'a14 a24 a34 a44 a41 a42 a43 '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a14

a14 isNil ifTrue: [a14 := nil].

^ a14! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a24

a24 isNil ifTrue: [a24 := nil].

^ a24! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a34

a34 isNil ifTrue: [a34 := nil].

^ a34! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a41

a41 isNil ifTrue: [a41 := nil].

^ a41! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a42

a42 isNil ifTrue: [a42 := nil].

^ a42! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a43

a43 isNil ifTrue: [a43 := nil].

^ a43! !

!ThreeDMatrix methodsFor: 'accessing' stamp: 'Ali Chamas 4/17/2001 17:25'!
a44

a44 isNil ifTrue: [a44 := nil].

^ a44! !


!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a14: value

a14 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a24: value

a24 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a34: value

a34 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a41: value

a41 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a42: value

a42 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a43: value

a43 := value! !

!ThreeDMatrix methodsFor: 'updating' stamp: 'Ali Chamas 4/17/2001 17:25'!
a44: value

a44 := value! !


TransformMatrix subclass: #TranslationMatrix
	instanceVariableNames: 'deltaX deltaY '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!TranslationMatrix commentStamp: 'Ali Chamas 4/4/2001 19:32' prior: 0!
I represent a translation transformation matrix.
I use two values for the delta X and the delta Y of translation.!


!TranslationMatrix methodsFor: 'accessing - delta' stamp: 'Ali Chamas 4/4/2001 17:49'!
deltaX

deltaX isNil ifTrue: [deltaX := nil].

^ deltaX! !

!TranslationMatrix methodsFor: 'accessing - delta' stamp: 'Ali Chamas 4/4/2001 17:49'!
deltaY

deltaY isNil ifTrue: [deltaY := nil].

^ deltaY! !


!TranslationMatrix methodsFor: 'updating - delta'!
deltaX: value 
	deltaX _ value.
	"update the appropriate elements values as well..."
	self a31: deltaX! !

!TranslationMatrix methodsFor: 'updating - delta'!
deltaY: value 
	deltaY _ value.
	"update the appropriate elements values as well..."
	self a32: deltaY! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TranslationMatrix class
	instanceVariableNames: ''!

!TranslationMatrix class methodsFor: 'instance creation'!
delta: delta 
"create a new instance from the given delta..."
	^ self deltaX: delta deltaY: delta! !

!TranslationMatrix class methodsFor: 'instance creation'!
deltaX: deltaX deltaY: deltaY 
"create a new instance with the given delta values..."
	| new |
	new _ self new.
	new deltaX: deltaX;
	 deltaY: deltaY.
	^ new! !


ShapeDistorter subclass: #WaveDistorter
	instanceVariableNames: 'xamount yamount '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Assignment1'!
!WaveDistorter commentStamp: 'Ali Chamas 4/12/2001 12:44' prior: 0!
I represent a simple wave distorter.
I have a xamount and yamount floating value from 0.0 - (any large number).
These will offset the x/y points along a sine wave.!


!WaveDistorter methodsFor: 'distorting'!
distort: polygon 
	polygon points do: 
		[:point | 
		point y: point y + (point x sin * self yamount).
		point x: point x + (point y sin * self xamount).]! !


!WaveDistorter methodsFor: 'accessing'!
xamount
	xamount isNil ifTrue: [xamount _ 0].
	^ xamount! !

!WaveDistorter methodsFor: 'accessing'!
yamount
	yamount isNil ifTrue: [yamount _ 0].
	^ yamount! !


!WaveDistorter methodsFor: 'updating' stamp: 'Ali Chamas 4/10/2001 18:25'!
xamount: value

xamount := value! !

!WaveDistorter methodsFor: 'updating' stamp: 'Ali Chamas 4/10/2001 18:25'!
yamount: value

yamount := value! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

WaveDistorter class
	instanceVariableNames: ''!

!WaveDistorter class methodsFor: 'instance creation' stamp: 'Ali Chamas 4/10/2001 18:27'!
xamount: xamount
	| n |
	n _ self new.
	n xamount: xamount.
	^ n! !

!WaveDistorter class methodsFor: 'instance creation' stamp: 'Ali Chamas 4/10/2001 18:27'!
xamount: xamount yamount: yamount
	| n |
	n _ self new.
	n xamount: xamount; yamount: yamount.
	^ n! !

!WaveDistorter class methodsFor: 'instance creation' stamp: 'Ali Chamas 4/10/2001 18:28'!
yamount: yamount 
	| n |
	n _ self new.
	n yamount: yamount.
	^ n! !


More information about the Squeak-dev mailing list