TerseMan challenge

Bob Arning arning at charm.net
Sun Jan 9 00:38:49 UTC 2000


On Fri, 7 Jan 2000 18:02:54 -0800 Dan Ingalls <Dan.Ingalls at disney.com> wrote:
>The challenge is this:  using Morphic and Squeak to best advantage, and leaving the appearance and feature set of Tetris essentially unchanged (and not just cramming everything into long lines with short variable names ;-), rewrite Tetris with a significantly lower number of linesOfCode.

Ok, here's mine (as a changeset to the 2.7 tetris). It

	reduces #linesOfCode from 524 to 291
	reduces #bytesOfCode from 4071 to 2399	"method for this metric is included"

Beyond this, I fear that readability will suffer.

Cheers,
Bob

========
'From Squeak2.7 of 5 January 2000 [latest update: #1761] on 8 January 2000 at 4:02:22 pm'!
"Change Set:		tetris2
Date:			8 January 2000
Author:			Bob Arning

my entry in the TerseMan challenge"!

AlignmentMorph subclass: #Tetris
	instanceVariableNames: 'board scoreDisplay '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!
Morph subclass: #TetrisBlock
	instanceVariableNames: 'angle shapeInfo board baseCellNumber '
	classVariableNames: 'ShapeChoices '
	poolDictionaries: ''
	category: 'Morphic-Games'!
PasteUpMorph subclass: #TetrisBoard
	instanceVariableNames: 'paused gameOver delay score currentBlock game '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Games'!

!ClassDescription methodsFor: 'private' stamp: 'RAA 1/8/2000 14:28'!
bytesOfCode  "InterpreterSimulator bytesOfCode 7476"
	"An approximate measure of lines of code.
	Includes comments, but excludes blank lines."

	| space |
	space _ 0.
	self selectorsDo: [:sel |
		space _ space + (self compiledMethodAt: sel) size.
	].
	self isMeta
		ifTrue: [^ space]
		ifFalse: [^ space + self class bytesOfCode]
"
(SystemOrganization categories select: [:c | 'Fabrik*' match: c]) detectSum:
		[:c | (SystemOrganization superclassOrder: c) detectSum: [:cl | cl bytesOfCode]] 
"! !


!Tetris methodsFor: 'initialization' stamp: 'RAA 1/8/2000 14:38'!
buildButtonTarget: aTarget label: aLabel selector: aSelector help: aString

	^self rowForButtons
		addMorph: (
			SimpleButtonMorph new 
				target: aTarget;
				label: aLabel;
				actionSelector: aSelector;
				borderColor: #raised;
				borderWidth: 2;
				color: color
		)

! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/7/2000 22:43'!
initialize

	super initialize.
	board _ TetrisBoard new game: self.
	color _ Color lightGray.
	orientation _ #vertical.
	centering _ #center.
	vResizing _ #shrinkWrap.
	hResizing _ #spaceFill.
	inset _ 3.
	self 
		addMorphBack: self makeGameControls;
		addMorphBack: self makeMovementControls;
		addMorphBack: self showScoreDisplay;
		addMorphBack: board.
	board newGame.

! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/7/2000 22:51'!
makeGameControls

	^self rowForButtons
		addMorph:
			(self
				buildButtonTarget: self
				label: 'Quit'
				selector: #delete
				help: 'quit');
		addMorph:
			(self
				buildButtonTarget: board
				label: 'Pause'
				selector: #pause
				help: 'pause');
		addMorph:
			(self
				buildButtonTarget: board
				label: 'New game'
				selector: #newGame
				help: 'new game')! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/8/2000 14:03'!
makeMovementControls

	^self rowForButtons
		addMorph:
			(self
				buildButtonTarget: board
				label: '->'
				selector: #moveRight
				help: 'move to the right');
		addMorph:
			(self
				buildButtonTarget: board
				label: ' ) '
				selector: #rotateClockWise
				help: 'rotate clockwise');
		addMorph:
			(self
				buildButtonTarget: board
				label: ' | '
				selector: #dropAllTheWay
				help: 'drop');
		addMorph:
			(self
				buildButtonTarget: board
				label: ' ( '
				selector: #rotateAntiClockWise
				help: 'rotate anticlockwise');
		addMorph:
			(self
				buildButtonTarget: board
				label: '<-'
				selector: #moveLeft
				help: 'move to the left')! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/7/2000 21:48'!
rowForButtons

	^AlignmentMorph newRow
		color: color;
		borderWidth: 0;
		inset: 3;
		vResizing: #shrinkWrap;
		centering: #center
! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/7/2000 21:50'!
showScoreDisplay

	^self rowForButtons
		hResizing: #rigid;
		addMorph: (
			self 
				wrapPanel: (
					(scoreDisplay _ LedMorph new) digits: 4; extent: (4*10 at 15)
				) 
				label: 'Score:'
		)
! !

!Tetris methodsFor: 'initialization' stamp: 'RAA 1/8/2000 14:38'!
wrapPanel: anLedPanel label: aLabel
	"wrap an LED panel in an alignmentMorph with a label to its left"

	^self rowForButtons
		color: color lighter;
		addMorph: anLedPanel;
		addMorph: (StringMorph contents: aLabel)
! !

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

!Tetris methodsFor: 'events' stamp: 'RAA 1/8/2000 15:42'!
keyStroke: evt

	| charValue |
	charValue _ evt keyCharacter asciiValue.
	charValue = 28 ifTrue: [board moveLeft].
	charValue = 29 ifTrue: [board moveRight].
	charValue = 30 ifTrue: [board rotateClockWise].
	charValue = 31 ifTrue: [board rotateAntiClockWise].
	charValue = 32 ifTrue: [board dropAllTheWay].
! !

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

!Tetris methodsFor: 'events' stamp: 'RAA 1/7/2000 22:37'!
score: anInteger

	scoreDisplay value: anInteger! !


!Tetris class methodsFor: 'as yet unclassified' stamp: 'RAA 1/7/2000 23:19'!
colors

	^{
		Color r: 0.5 g: 0 b: 0.
		Color r: 0 g: 0.5 b: 0.
		Color r: 0 g: 0 b: 0.5.
		Color r: 0.5 g: 0.5 b: 0.
		Color r: 0.5 g: 0 b: 0.5.
		Color r: 0 g: 0.5 b: 0.5
	}
! !


!TetrisBlock methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 15:58'!
board: theBoard

	board _ theBoard.
	4 timesRepeat: [
		self addMorph: (
			RectangleMorph new
				color: color;
				extent: board cellSize;
				borderRaised
		 )
	].
	self positionCellMorphs.! !

!TetrisBlock methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 12:37'!
dropByOne
 
	^self moveDeltaX: 0 deltaY: 1 deltaAngle: 0! !

!TetrisBlock methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 15:33'!
initialize

	super initialize.
	bounds _ (2 at 2) negated extent: 1 at 1.	"keep this puppy out of sight"
	shapeInfo _ self class shapeChoices atRandom.
	baseCellNumber _ (4 atRandom + 2) @ 1.
	angle _ 4 atRandom.
	color _ Tetris colors atRandom.
! !

!TetrisBlock methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 13:56'!
moveDeltaX: deltaX deltaY: deltaY deltaAngle: deltaAngle 

	| delta |

	delta _ deltaX @ deltaY.
	(shapeInfo atWrap: angle + deltaAngle) do: [ :offsetThisCell | 
		(board emptyAt: baseCellNumber + offsetThisCell + delta) ifFalse: [^ false]
	].
	baseCellNumber _ baseCellNumber + delta.
	angle _ angle + deltaAngle - 1 \\ 4 + 1.
	self positionCellMorphs.
	^ true ! !

!TetrisBlock methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 13:41'!
positionCellMorphs

	(shapeInfo atWrap: angle) withIndexDo: [ :each :index |
		(submorphs at: index)
			position: (board originForCell: baseCellNumber + each)
	].
	fullBounds _ nil.
	self changed.
	 
! !


!TetrisBlock class methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 15:29'!
flipShapes: anArray

	^OrderedCollection new 
		add: anArray;
		add: (anArray collect: [ :each | each y negated @ each x]);
		add: (anArray collect: [ :each | each x negated @ each y negated]);
		add: (anArray collect: [ :each | each y @ each x negated]);
		yourself
	
! !

!TetrisBlock class methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 11:55'!
includeInNewMorphMenu

	^false! !

!TetrisBlock class methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 15:32'!
shapeChoices

	^ ShapeChoices ifNil: [
		ShapeChoices _ {
			{ {  0 @ 0 .  1 @ 0 .  0 @ 1 .  1 @ 1  } }.	"square - one is sufficient here"
			self flipShapes: {  0 @  0 . -1 @  0 .  1 @  0 .  0 @ -1  }.	"T"
			{ 
				{  0 @ 0 . -1 @ 0 .  1 @ 0 .  2 @ 0  }.
				{  0 @ 0 .  0 @-1 .  0 @ 1 .  0 @ 2  } 	"long - two are sufficient here"
			}.
			self flipShapes: { 0 @ 0 .  0 @ -1 .  0 @  1 .  1 @  1  }.	"L"
			self flipShapes: { 0 @ 0 .  0 @ -1 .  0 @  1 . -1 @  1  }.	"inverted L"
			self flipShapes: { 0 @ 0 . -1 @  0 .  0 @ -1 .  1 @ -1  }.	"S"
			self flipShapes: {  0 @ 0 .  1 @ 0 .  0 @ -1 . -1 @ -1  } "Z"
		}.
	]
! !


!TetrisBoard methodsFor: 'initialization' stamp: 'RAA 1/8/2000 13:26'!
initialize

	super initialize.
	resizeToFit _ false.
	bounds _ 0 at 0 extent: (self numColumns @ self numRows) * self cellSize + (1 at 1).
	color _ Color r: 0.8 g: 1.0 b: 1.0.
! !

!TetrisBoard methodsFor: 'stepping' stamp: 'RAA 1/8/2000 15:59'!
step

	(self ownerThatIsA: HandMorph) ifNotNil: [^self].
	paused ifTrue: [^ self]. 
	currentBlock ifNil: [
		currentBlock _ TetrisBlock new.
		self addMorphFront: currentBlock.
		currentBlock board: self.
	] ifNotNil: [
		currentBlock dropByOne ifFalse: [self storePieceOnBoard]
	].
! !

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

	^ delay! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 14:03'!
dropAllTheWay

	self running ifFalse: [^ self].
	[currentBlock dropByOne] whileTrue: [
		self score: score + 1
	].
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 11:17'!
moveLeft

	self running ifFalse: [^ self].
	currentBlock moveDeltaX: -1 deltaY: 0 deltaAngle: 0.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 11:17'!
moveRight

	self running ifFalse: [^ self].
	currentBlock moveDeltaX: 1 deltaY: 0 deltaAngle: 0.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 13:20'!
newGame

	self removeAllMorphs.
	gameOver _ paused _ false.
	delay _ 500.
	currentBlock _ nil.
	self score: 0.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 11:16'!
pause

	gameOver ifTrue: [^ self].
	paused _ paused not.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 11:17'!
rotateAntiClockWise

	self running ifFalse: [^ self].
	currentBlock moveDeltaX: 0 deltaY: 0 deltaAngle: -1.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 1/8/2000 11:17'!
rotateClockWise

	self running ifFalse: [^ self].
	currentBlock moveDeltaX: 0 deltaY: 0 deltaAngle: 1.
! !

!TetrisBoard methodsFor: 'button actions' stamp: 'RAA 8/28/1999 22:31'!
running

	^currentBlock notNil and: [paused not]! !

!TetrisBoard methodsFor: 'other' stamp: 'RAA 1/8/2000 13:20'!
checkForFullRows

	| targetY morphsInRow bonus |
	self numRows to: 2 by: -1 do: [ :row |
		targetY _ (self originForCell: 1 at row) y.
		[
			morphsInRow _ self submorphsSatisfying: [ :each | each top = targetY].
			morphsInRow size = self numColumns
		] whileTrue: [
			bonus _ (morphsInRow collect: [:each | each color]) asSet size = 1 
				ifTrue: [1000] 
				ifFalse: [100].
			self score: score + bonus.
			submorphs copy do: [ :each |
				each top = targetY ifTrue: [
					each delete
				].
				each top < targetY ifTrue: [
					each position: each position + (0 at self cellSize y)
				].
			].
		].
	].

! !

!TetrisBoard methodsFor: 'other' stamp: 'RAA 1/8/2000 13:59'!
storePieceOnBoard

	currentBlock submorphs do: [ :each |
		self addMorph: each.
		((each top - self top) // self cellSize y) < 3 ifTrue: [
			paused _ gameOver _ true.
		].
	].
	currentBlock delete.
	currentBlock _ nil.
	self checkForFullRows.
	self score: score + 10.
	delay _ delay - 2 max: 80.

! !

!TetrisBoard methodsFor: 'data' stamp: 'RAA 1/8/2000 13:16'!
emptyAt: aPoint

	| cellOrigin |
	(aPoint x between: 1 and: self numColumns) ifFalse: [^ false].
	(aPoint y < 1) ifTrue: [^ true].	"handle early phases"
	(aPoint y <= self numRows) ifFalse: [^ false].
	cellOrigin _ self originForCell: aPoint.
	^(self submorphsSatisfying: [ :each | each topLeft = cellOrigin]) isEmpty

! !

!TetrisBoard methodsFor: 'data' stamp: 'RAA 8/28/1999 23:29'!
numColumns

	^10
	! !

!TetrisBoard methodsFor: 'data' stamp: 'RAA 8/28/1999 23:30'!
numRows

	^27
	! !

!TetrisBoard methodsFor: 'accessing' stamp: 'RAA 1/7/2000 22:34'!
game: aTetris

	game _ aTetris! !

!TetrisBoard methodsFor: 'accessing' stamp: 'RAA 1/7/2000 22:38'!
score: aNumber

	score _ aNumber.
	game score: score.! !

!TetrisBoard methodsFor: 'as yet unclassified' stamp: 'RAA 1/7/2000 23:12'!
cellSize

	^12 at 12! !

!TetrisBoard methodsFor: 'as yet unclassified' stamp: 'RAA 1/8/2000 13:11'!
originForCell: aPoint

	^aPoint - (1 at 1) * self cellSize + self position

! !


!TetrisBoard class methodsFor: 'as yet unclassified' stamp: 'RAA 1/7/2000 22:56'!
includeInNewMorphMenu

	^false! !


Tetris removeSelector: #mouseLeave:!
Tetris removeSelector: #buildButton:target:label:selector:!
Tetris removeSelector: #scoreDisplay!
Tetris removeSelector: #board!
TetrisBlock removeSelector: #tetris:!
TetrisBlock class removeSelector: #squareShape!
TetrisBlock class removeSelector: #teeShape!
TetrisBlock class removeSelector: #invertedEllShape!
TetrisBlock class removeSelector: #ellShape!
TetrisBlock class removeSelector: #longShape!
TetrisBlock class removeSelector: #zeeShape!
TetrisBlock class removeSelector: #test:!
TetrisBlock class removeSelector: #essShape!
TetrisBoard removeSelector: #colors!
TetrisBoard removeSelector: #checkRow!
TetrisBoard removeSelector: #blockInfo!
TetrisBoard removeSelector: #makeNewPiece!
TetrisBoard removeSelector: #boardArray!
TetrisBoard removeSelector: #dropByOne!
TetrisBoard removeSelector: #paint!
TetrisBoard removeSelector: #drop!
TetrisBoard removeSelector: #withScoreDisplay:!
TetrisBoard class removeSelector: #withScoreDisplay:!
"Postscript:
Leave the line above, and replace the rest of this comment by a useful one.
Executable statements should follow this comment, and should
be separated by periods, with no exclamation points (!!).
Be sure to put any further comments in double-quotes, like this one."

StringHolder new
	contents: 'evaluate:

Tetris linesOfCode + TetrisBlock linesOfCode + TetrisBoard linesOfCode

Tetris bytesOfCode + TetrisBlock bytesOfCode + TetrisBoard bytesOfCode

while the original produced:

Tetris linesOfCode + TetrisBoard linesOfCode  524
Tetris bytesOfCode + TetrisBoard bytesOfCode 4071
';
	openLabel: 'TerseMan Tetris challenge'!





More information about the Squeak-dev mailing list