Tetris

Aibek Musaev abbey at cc.gatech.edu
Sat Aug 28 19:17:13 UTC 1999


I hope some of you will find this little project useful. Here is the
preamble from the attached changeSet:

"Change Set:		Tetris
Date:			31 July 1999
Author:			Aibek Musaev (abbey at cc.gatech.edu)

This is a port of JTetris.java 1.0.0.

How to start:
choose new morph.../Games/Tetris

How to play:
1) using buttons
2) using keyboard:
	drop - spacebar
	move to left - left arrow
	move to right - right arrow
	rotate clockwise - up arrow
	rotate anticlockwise - down arrow
	NOTE: mouse must be over Tetris!
"

Content-Type: TEXT/PLAIN; charset=US-ASCII; name="Tetris.28Aug253pm.cs"
Content-ID: <Pine.SUN.3.96.990828151713.1135E at felix.cc.gatech.edu>
Content-Description: 

'From Squeak 2.3 of January 14, 1999 on 28 August 1999 at 2:53:25 pm'!
"Change Set:		Tetris
Date:			31 July 1999
Author:			Aibek Musaev (abbey at cc.gatech.edu)

This is a port of JTetris.java 1.0.0.

How to start:
choose new morph.../Games/Tetris

How to play:
1) using buttons
2) using keyboard:
	drop - spacebar
	move to left - left arrow
	move to right - right arrow
	rotate clockwise - up arrow
	rotate anticlockwise - down arrow
	NOTE: mouse must be over Tetris!!
"!

AlignmentMorph subclass: #Tetris
	instanceVariableNames: 'board scoreDisplay '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!
Morph subclass: #TetrisBoard
	instanceVariableNames: 'boardArray colors paused gameOver currentBlockX currentBlockY currentBlockColor currentBlockShape currentBlockAngle nextBlockX nextBlockY nextBlockColor nextBlockShape nextBlockAngle delay blockInfo scoreDisplay score '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!

!Tetris methodsFor: 'access' stamp: 'am 8/22/1999 11:07'!
board

	board ifNil: [
		board _ TetrisBoard withScoreDisplay: self scoreDisplay.
	].
	^ board
! !

!Tetris methodsFor: 'access' stamp: 'am 8/22/1999 10:50'!
scoreDisplay

	scoreDisplay ifNil: [
		scoreDisplay _ LedMorph new
			digits: 4;
			extent: (4*10 at 15).
	].
	^ scoreDisplay
! !

!Tetris methodsFor: 'initialization' stamp: 'AM 8/2/1999 12:07'!
buildButton: aButton target: aTarget label: aLabel selector: aSelector
	"wrap a button or switch in an alignmentMorph to allow a row of buttons to fill space"

	| a |
	aButton 
		target: aTarget;
		label: aLabel;
		actionSelector: aSelector;
		borderColor: #raised;
		borderWidth: 2;
		color: color.
	a _ AlignmentMorph newColumn
		centering: #center;
		hResizing: #spaceFill;
		vResizing: #shrinkWrap;
		color: color.
	a addMorph: aButton.
	^ a

! !

!Tetris methodsFor: 'initialization' stamp: 'am 8/22/1999 10:55'!
initialize

	super initialize.
	color _ Color lightGray.
	orientation _ #vertical.
	centering _ #center.
	vResizing _ #shrinkWrap.
	hResizing _ #spaceFill.
	inset _ 3.
	self addMorph: self board.
	self addMorph: self showScoreDisplay.
	self addMorph: self makeMovementControls.
	self addMorph: self makeGameControls.
! !

!Tetris methodsFor: 'initialization' stamp: 'am 8/8/1999 15:10'!
makeGameControls

	| row but |
	row _ AlignmentMorph newRow
		color: color;
		borderWidth: 0;
		inset: 3.
	row hResizing: #spaceFill; vResizing: #shrinkWrap; centering: #center; extent: 5 at 5.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self
			label: 'Quit'
			selector: #delete).
	but setBalloonText: 'quit'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: 'Pause'
			selector: #pause).
	but setBalloonText: 'pause'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: 'New game'
			selector: #newGame).
	but setBalloonText: 'new game'.
	^ row
! !

!Tetris methodsFor: 'initialization' stamp: 'am 8/8/1999 13:56'!
makeMovementControls

	| row but |
	row _ AlignmentMorph newRow
		color: color;
		borderWidth: 0;
		inset: 3.
	row hResizing: #spaceFill; vResizing: #shrinkWrap; centering: #center; extent: 5 at 5.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: '->'
			selector: #moveRight).
	but setBalloonText: 'move to the right'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: ' ) '
			selector: #rotateClockWise).
	but setBalloonText: 'rotate clockwise'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: ' | '
			selector: #drop).
	but setBalloonText: 'drop'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: ' ( '
			selector: #rotateAntiClockWise).
	but setBalloonText: 'rotate anticlockwise'.
	row addMorph:
		(but _ self
			buildButton: SimpleButtonMorph new
			target: self board
			label: '<-'
			selector: #moveLeft).
	but setBalloonText: 'move to the left'.
	^ row
! !

!Tetris methodsFor: 'initialization' stamp: 'am 8/22/1999 11:15'!
showScoreDisplay

	| row |
	row _ AlignmentMorph newRow
		color: color;
		borderWidth: 0;
		inset: 3.
	row hResizing: #rigid; vResizing: #shrinkWrap; centering: #center; extent: 5 at 5.
	row addMorph: (self wrapPanel: self scoreDisplay label: 'Score:').
	^ row
! !

!Tetris methodsFor: 'initialization' stamp: 'am 8/22/1999 11:12'!
wrapPanel: anLedPanel label: aLabel
	"wrap an LED panel in an alignmentMorph with a label to its left"

	| a |
	a _ AlignmentMorph newRow
		centering: #center;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap;
		borderWidth: 0;
		inset: 3;
		color: color lighter.
	a addMorph: anLedPanel.
	a addMorph: (StringMorph contents: aLabel). 
	^ a

! !

!Tetris methodsFor: 'events' stamp: 'am 8/28/1999 14:22'!
handlesMouseOver: evt
	^ true
! !

!Tetris methodsFor: 'events' stamp: 'am 8/28/1999 14:21'!
keyStroke: evt
        | char |
        char _ evt keyCharacter.
        char asciiValue = 28 ifTrue: [board moveLeft].
        char asciiValue = 29 ifTrue: [board moveRight].
        char asciiValue = 30 ifTrue: [board rotateClockWise].
        char asciiValue = 31 ifTrue: [board rotateAntiClockWise].
        char asciiValue = 32 ifTrue: [board drop].
! !

!Tetris methodsFor: 'events' stamp: 'am 8/28/1999 14:22'!
mouseEnter: evt
        evt hand newKeyboardFocus: self
! !

!Tetris methodsFor: 'events' stamp: 'am 8/28/1999 14:22'!
mouseLeave: evt
        evt hand newKeyboardFocus: nil
! !


!TetrisBoard methodsFor: 'initialization' stamp: 'am 8/22/1999 11:10'!
initialize

	| numColumns numRows |
	super initialize.

	paused _ gameOver _ false.
	currentBlockX _ currentBlockY _ currentBlockColor _ nextBlockX _ nextBlockY _ nextBlockColor _ score _ 0.
	delay _ 500.
	blockInfo _ self blockInfo.
	boardArray _ self boardArray.
	colors _ self colors.

	numColumns _ boardArray size.
	numRows _ boardArray first size.
	self extent: (numColumns * 12 + 1) @ (numRows * 12 + 1).
	self color: (colors at: 1 + 0).
"	self newGame."
! !

!TetrisBoard methodsFor: 'initialization' stamp: 'am 8/22/1999 11:11'!
withScoreDisplay: aScoreDisplay

	scoreDisplay _ aScoreDisplay.
	self newGame.
! !

!TetrisBoard methodsFor: 'stepping' stamp: 'am 8/4/1999 18:01'!
step

	paused ifTrue: [^ self].
	(currentBlockColor = 0)
		ifTrue: [" make a new piece "
			(nextBlockColor = 0) ifTrue: [self makeNewPiece].
			currentBlockColor _ nextBlockColor.
			currentBlockX _ nextBlockX.
			currentBlockY _ nextBlockY.
			currentBlockShape _ nextBlockShape.
			currentBlockAngle _ nextBlockAngle.
			self makeNewPiece.
		]
		ifFalse: [" drop the current piece by one place "
			self dropByOne.
		].
	self paint.
! !

!TetrisBoard methodsFor: 'stepping' stamp: 'AM 7/26/1999 16:07'!
stepTime

	^ delay! !

!TetrisBoard methodsFor: 'drawing' stamp: 'am 8/3/1999 20:18'!
paint

	| i r rx ry numColumns numRows x y |
	numColumns _ boardArray size.
	numRows _ boardArray first size.
	self removeAllMorphs.
	x _ 0.
	[x < numColumns] whileTrue: [
		y _ 0.
		[y < numRows] whileTrue: [
			((boardArray at: 1 + x) at: 1 + y) ~= 0 ifTrue: [
				r _ RectangleMorph new.
				r
					color: (colors at: 1 + ((boardArray at: 1 + x) at: 1 + y));
					extent: 12 @ 12;
					borderRaised.
				rx _ x * 12.
				ry _ y * 12.
				r position: (self position + (rx @ ry)).
				self addMorph: r.
			].
			y _ y + 1.
		].
		x _ x + 1.
	].

	currentBlockColor ~= 0 ifTrue: [
		i _ -1.
		[i < 3] whileTrue: [
			i _ i + 1.
			r _ RectangleMorph new.
			r
				color: (colors at: 1 + currentBlockColor);
				extent: 12 @ 12;
				borderRaised.
			rx _ (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)) * 12.
			ry _ (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1)) * 12.
			r position: (self position + (rx @ ry)).
			self addMorph: r.
		].
	].
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'am 8/8/1999 14:54'!
drop

	| i numRows |
	(paused not) ifTrue: [
		numRows _ boardArray first size.
		[true] whileTrue: [
			i _ -1.
			[i < 3] whileTrue: [
				i _ i + 1.
				((currentBlockY + 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1)) > (numRows - 1))
					ifTrue: [
						self paint.
						"dopaint();"
						^ self.
					]
					ifFalse: [
						(((boardArray at: 1 + (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)))
										at: 1 + (currentBlockY + 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [
							self paint.
							"dopaint();"
							^ self.
						].
					].
			].
			currentBlockY _ currentBlockY + 1.
			score _ score + 1.
		].
	].
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'AM 8/2/1999 11:45'!
moveLeft

	| i |
	i _ -1.
	(paused not) ifTrue: [
		[i < 3] whileTrue: [
			i _ i + 1.
			((currentBlockX - 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)) < 0)
				ifTrue: [^ self]
				ifFalse: [
					(((boardArray at: 1 + (currentBlockX - 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)))
									at: 1 + (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [^ self].
				].
		].
		currentBlockX _ currentBlockX - 1.
		self paint.
		"dopaint();"
	].
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'AM 8/2/1999 11:45'!
moveRight

	| i numColumns |
	i _ -1.
	(paused not) ifTrue: [
		numColumns _ boardArray size.
		[i < 3] whileTrue: [
			i _ i + 1.
			((currentBlockX + 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)) > (numColumns - 1))
				ifTrue: [^ self]
				ifFalse: [
					(((boardArray at: 1 + (currentBlockX + 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0)))
									at: 1 + (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [^ self].
				].
		].
		currentBlockX _ currentBlockX + 1.
		self paint.
		"dopaint();"
	].! !

!TetrisBoard methodsFor: 'button actions' stamp: 'am 8/8/1999 14:53'!
newGame

	| x y numColumns numRows |
	x _ 0.
	numColumns _ boardArray size.
	numRows _ boardArray first size.
	[x < numColumns] whileTrue: [
		y _ 0.
		[y < numRows] whileTrue: [
			(boardArray at: 1 + x) at: 1 + y put: 0.
			y _ y + 1.
		].
		x _ x + 1.
	].
	gameOver _ paused _ false.
	delay _ 500.

	currentBlockColor _ nextBlockColor _ 0.
	self score: 0.
	"getParent().action(new Event(this, score, null), this);
     repaint();"
	self paint.! !

!TetrisBoard methodsFor: 'button actions' stamp: 'AM 8/2/1999 11:46'!
pause

	gameOver ifTrue: [^ self].
	paused _ paused not.
	"repaint();"
	self paint.! !

!TetrisBoard methodsFor: 'button actions' stamp: 'AM 8/2/1999 11:46'!
rotateAntiClockWise

	| i newBlockAngle numColumns numRows |

	(paused not) ifTrue: [
		newBlockAngle _ currentBlockAngle - 1.
		(newBlockAngle = -1) ifTrue: [newBlockAngle _ 3].
		i _ -1.
		numColumns _ boardArray size.
		numRows _ boardArray first size.
		[i < 3] whileTrue: [
			i _ i + 1.
			((currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)) > (numColumns - 1))
				ifTrue: [^ self]
				ifFalse: [
					((currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)) < 0)
						ifTrue: [^ self]
						ifFalse: [
							((currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1)) > (numRows - 1))
								ifTrue: [^ self]
								ifFalse: [
									((currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1)) < 0)
										ifTrue: [^ self]
										ifFalse: [
											(((boardArray at: 1 + (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)))
															at: 1 + (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [^ self].
										].
								].
						].
				].
		].
		currentBlockAngle _ newBlockAngle.
		"dopaint();"
		self paint.
	].
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'AM 8/2/1999 11:46'!
rotateClockWise

	| i newBlockAngle numColumns numRows |

	(paused not) ifTrue: [
		newBlockAngle _ currentBlockAngle + 1.
		(newBlockAngle = 4) ifTrue: [newBlockAngle _ 0].
		i _ -1.
		numColumns _ boardArray size.
		numRows _ boardArray first size.
		[i < 3] whileTrue: [
			i _ i + 1.
			((currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)) > (numColumns - 1))
				ifTrue: [^ self]
				ifFalse: [
					((currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)) < 0)
						ifTrue: [^ self]
						ifFalse: [
							((currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1)) > (numRows - 1))
								ifTrue: [^ self]
								ifFalse: [
									((currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1)) < 0)
										ifTrue: [^ self]
										ifFalse: [
											(((boardArray at: 1 + (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 0)))
															at: 1 + (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + newBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [^ self].
										].
								].
						].
				].
		].
		currentBlockAngle _ newBlockAngle.
		"dopaint();"
		self paint.
	].
! !

!TetrisBoard methodsFor: 'other' stamp: 'am 8/22/1999 11:06'!
checkRow

	| i row colour j numColumns numRows break |
	numColumns _ boardArray size.
	numRows _ boardArray first size.
	row _ numRows.
	colour _ 0.
	[row > 0] whileTrue: [
		row _ row - 1.
		i _ -1.
		break _ false.
		[(i < (numColumns - 1)) & (break not)] whileTrue: [
			i _ i + 1.
			((boardArray at: 1 + i) at: 1 + row) = 0
				ifTrue: [break _ true]
				ifFalse: [
					(i = 0)
						ifTrue: [colour _ (boardArray at: 1 + i) at: 1 + row]
						ifFalse: [
							colour ~= ((boardArray at: 1 + i) at: 1 + row) ifTrue: [
								colour _ 0.
							].
						].
				].
		].
		break ifFalse: [
			j _ row.
			row _ row + 1.
			j _ j - 1.
			[j > 0] whileTrue: [
				i _ -1.
				[i < (numColumns - 1)] whileTrue: [
					i _ i + 1.
					(boardArray at: 1 + i) at: 1 + (j + 1) put: ((boardArray at: 1 + i) at: 1 + j).
				].
				j _ j - 1.
			].
			colour = 0
				ifTrue: [self score: (score + 100)]
				ifFalse: [self score: (score + 1000)].
			"repaint();"
			self paint.
		].
	].
! !

!TetrisBoard methodsFor: 'other' stamp: 'am 8/3/1999 20:16'!
dropByOne

	| i breakLoop numRows |
	i _ -1.
	breakLoop _ false.
	numRows _ boardArray first size.
	[(i < 3) & (breakLoop not)] whileTrue: [
		i _ i + 1.
		(currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1) >= (numRows - 1))
			ifTrue: [
				self storePieceOnBoard.
				breakLoop _ true.
			]
			ifFalse: [
				(((boardArray at: 1 + (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0))) at: 1 + (currentBlockY + 1 + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1))) ~= 0) ifTrue: [
					self storePieceOnBoard.
					breakLoop _ true.
				].
			].
	].
	currentBlockY _ currentBlockY + 1.
! !

!TetrisBoard methodsFor: 'other' stamp: 'am 8/4/1999 18:02'!
makeNewPiece

	nextBlockColor _ 6 atRandom + 1.
	nextBlockColor = 7 ifTrue: [nextBlockColor _ 1].
	nextBlockX _ 4 atRandom + 3.
	nextBlockX = 7 ifTrue: [nextBlockX _ 1].
	nextBlockY _ 1.
	nextBlockShape _ 7 atRandom.
	nextBlockShape = 7 ifTrue: [nextBlockShape _ 0].
	nextBlockAngle _ 4 atRandom.
	nextBlockAngle = 4 ifTrue: [nextBlockAngle _ 0].
	"getParent().action(new Event(this, -1, null), this);"
! !

!TetrisBoard methodsFor: 'other' stamp: 'am 8/8/1999 14:51'!
storePieceOnBoard

	| i |
	i _ -1.
	[i < 3] whileTrue: [
		i _ i + 1.
		(boardArray at: 1 + (currentBlockX + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 0))) at: 1 + (currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1)) put: currentBlockColor.
		(currentBlockY + ((((blockInfo at: 1 + currentBlockShape) at: 1 + currentBlockAngle) at: 1 + i) at: 1 + 1) < 3) ifTrue: [
			paused _ true.
			gameOver _ true.
		].
	].
	self checkRow.
	self score: (score + 10).
	(delay > 80) ifTrue: [delay _ delay - 2].
	currentBlockColor _ 0.
! !

!TetrisBoard methodsFor: 'data' stamp: 'am 8/8/1999 13:43'!
blockInfo

	^ {
                          { { { 0. 0 }. { 1. 0 }. { 0. 1 }. { 1. 1 } }. " Square "
                            { { 0. 0 }. { 1. 0 }. { 0. 1 }. { 1. 1 } }.
                            { { 0. 0 }. { 1. 0 }. { 0. 1 }. { 1. 1 } }.
                            { { 0. 0 }. { 1. 0 }. { 0. 1 }. { 1. 1 } } }.
                          { { { 0. 0 }. {-1. 0 }. { 1. 0 }. { 0.-1 } }. " T "
                            { { 0. 0 }. { 0. 1 }. { 1. 0 }. { 0.-1 } }.
                            { { 0. 0 }. { 0. 1 }. { 1. 0 }. {-1. 0 } }.
                            { { 0. 0 }. { 0. 1 }. { 0.-1 }. {-1. 0 } } }.
                          { { { 0. 0 }. {-1. 0 }. { 1. 0 }. { 2. 0 } }. " | "
                            { { 0. 0 }. { 0.-1 }. { 0. 1 }. { 0. 2 } }.
                            { { 0. 0 }. {-1. 0 }. { 1. 0 }. { 2. 0 } }.
                            { { 0. 0 }. { 0.-1 }. { 0. 1 }. { 0. 2 } } }.
                          { { { 0. 0 }. { 0.-1 }. { 0. 1 }. { 1. 1 } }. " L "
                            { { 0. 0 }. { 1. 0 }. {-1. 0 }. {-1. 1 } }.
                            { { 0. 0 }. { 0. 1 }. { 0.-1 }. {-1.-1 } }.
                            { { 0. 0 }. {-1. 0 }. { 1. 0 }. { 1.-1 } } }.
                          { { { 0. 0 }. { 0.-1 }. { 0. 1 }. {-1. 1 } }. " Inverted L "
                            { { 0. 0 }. { 1. 0 }. {-1. 0 }. {-1.-1 } }.
                            { { 0. 0 }. { 0. 1 }. { 0.-1 }. { 1.-1 } }.
                            { { 0. 0 }. {-1. 0 }. { 1. 0 }. { 1. 1 } } }.
                          { { { 0. 0 }. {-1. 0 }. { 0.-1 }. { 1.-1 } }. " S "
                            { { 0. 0 }. { 0.-1 }. { 1. 0 }. { 1. 1 } }.
                            { { 0. 0 }. {-1. 0 }. { 0.-1 }. { 1.-1 } }.
                            { { 0. 0 }. { 0.-1 }. { 1. 0 }. { 1. 1 } } }.
                          { { { 0. 0 }. { 1. 0 }. { 0.-1 }. {-1.-1 } }. " Z "
                            { { 0. 0 }. { 0. 1 }. { 1. 0 }. { 1.-1 } }.
                            { { 0. 0 }. { 1. 0 }. { 0.-1 }. {-1.-1 } }.
                            { { 0. 0 }. { 0. 1 }. { 1. 0 }. { 1.-1 } } } 
	}.
! !

!TetrisBoard methodsFor: 'data' stamp: 'am 8/8/1999 13:41'!
boardArray

	| tmpArray |
	tmpArray _ Array new: 10.
	1 to: 10 do: [:i |
		tmpArray at: i put: (Array new: 27).
	].
	1 to: 10 do: [:i |
		1 to: 27 do: [:j |
			(tmpArray at: i) at: j put: 0.
		].
	].
	^ tmpArray
! !

!TetrisBoard methodsFor: 'data' stamp: 'AM 8/1/1999 23:12'!
colors

	| tmp |
	tmp _ Array new: 7.
	tmp at: 1 put: (Color r: 0.8 g: 1.0 b: 1.0).
	tmp at: 2 put: (Color r: 0.5 g: 0 b: 0).
	tmp at: 3 put: (Color r: 0 g: 0.5 b: 0).
	tmp at: 4 put: (Color r: 0 g: 0 b: 0.5).
	tmp at: 5 put: (Color r: 0.5 g: 0.5 b: 0).
	tmp at: 6 put: (Color r: 0.5 g: 0 b: 0.5).
	tmp at: 7 put: (Color r: 0 g: 0.5 b: 0.5).
	^ tmp
! !

!TetrisBoard methodsFor: 'accessing' stamp: 'am 8/22/1999 11:06'!
score: aNumber
	score _ aNumber.
	scoreDisplay value: aNumber! !


!TetrisBoard class methodsFor: 'instance creation' stamp: 'am 8/22/1999 10:57'!
withScoreDisplay: aScoreDisplay
	^ self new withScoreDisplay: aScoreDisplay! !





More information about the Squeak-dev mailing list