[comp.lang.smalltalk] Tower of Hanoi Game

kww@cs.glasgow.ac.uk (Dr Kevin Waite) (11/27/90)

Here is an implementation of the Towers-of-Hanoi game that I think would
be a useful example of the MVC is action.   (BTW, did anyone outside the UK
get my earlier posting of the Montana game?).   Please note that this software
is purely educational - I REALLY don't spend all my time hacking games.
I hope you find it useful.


--------------------------------   C U T     H E R E    -------------------------


Object subclass: #Disk
	instanceVariableNames: 'size '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tower-of-Hanoi'!
Disk comment:
'My instances represent the circular disks that are used in the Towers-of-Hanoi game.  Their only attribute is their size which is expressed as a natural number.   In a game, each size is unique.'!


!Disk methodsFor: 'accessing'!

size
	^size!

size: aNaturalNumber
	"Sets the size of the receiver to be a value in
	the range [1, +oo)."

	size := aNaturalNumber max: 1.! !

!Disk methodsFor: 'testing'!

> otherDisk
	"Is the receiver bigger than otherDisk?"

	^self size > otherDisk size! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Disk class
	instanceVariableNames: ''!


!Disk class methodsFor: 'instance creation'!

ofSize: aSize
	^self new size: aSize! !

MouseMenuController subclass: #TowersOfHanoiController
	instanceVariableNames: ''
	classVariableNames: 'HanoiMenu '
	poolDictionaries: ''
	category: 'Tower-of-Hanoi'!
TowersOfHanoiController comment:
'My instances are used to handle user input in the TowersOfHanoi game.   I provide a menu that allows the user to reset the game and have it played automatically.   My red button can be used to manually select the towers that will be the source and destination of a move operation.'!


!TowersOfHanoiController methodsFor: 'control defaults'!

isControlActive
	"I am in control so long as the cursor is within my
	view's display area and the right mouse button is not
	pressed."

	^(view containsPoint: sensor cursorPoint) & sensor blueButtonPressed not! !

!TowersOfHanoiController methodsFor: 'menus'!

menu
	^HanoiMenu! !

!TowersOfHanoiController methodsFor: 'mouse activity'!

complain
	"The user has made an illegal movement selection.
	Flash my view to indicate my annoyance and wait
	for the user to release my mouse button."

	self view flash.
	Sensor waitNoButton.!

redButtonActivity
	"This method allows the user to play the game
	by indicating the source and destination towers
	using the mouse.  Pressing down the left button
	selects the source; releasing the button selects
	the destination.   If the move is illegal for any 
	reason then complain."

	| source dest |

	source := self towerAtCurrentPosition.
	(source isNil or: [source isEmpty]) ifTrue: [^self complain].

	Cursor hand showWhile: [Sensor waitNoButton].
	dest := self towerAtCurrentPosition.
	(dest isNil or: [dest == source]) ifTrue: [^self complain].

	(dest willAccept: source topDisk) ifFalse: [^self complain].

	self model moveDiskFrom: source to: dest.!

towerAtCurrentPosition
	"This method returns the tower currently pointed at by the
	cursor.  If there is no tower at this location then return nil."

	| locus width |

	locus := Sensor cursorPoint.
	(self view insetDisplayBox containsPoint: locus) ifFalse: [^nil].

	width := self view class towerWidth.
	self model towers do: [:tower |
		| centre xMin xMax |

		centre := self view xPositionOfTower: tower.
		xMin := centre - (width // 2).
		xMax := xMin + width.
		((xMin <= locus x) and: [locus x <= xMax]) ifTrue: [^tower].
	].
	^nil!

yellowButtonActivity
	| action index |

	index := self menu startUpYellowButton.
	action := index = 0 ifTrue: [nil] ifFalse: [self menu selectorAt: index].
	action notNil ifTrue: [model perform: action].! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TowersOfHanoiController class
	instanceVariableNames: ''!


!TowersOfHanoiController class methodsFor: 'initialize-release'!

initialize	
	"TowersOfHanoiController initialize."

	super initialize.
	HanoiMenu := ActionMenu
		labels: 'Restart Game\Auto Play' withCRs
		selectors: #(reset autoPlay)! !

TowersOfHanoiController initialize!


Object subclass: #TowersOfHanoi
	instanceVariableNames: 'towers numberOfDisks moves '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tower-of-Hanoi'!
TowersOfHanoi comment:
'My instances hold the state of play of a Tower-of-Hanoi game.   Their instance variables hold the three towers used to hold the disks (as an array) and a counter recording how many disks are being used.'!


!TowersOfHanoi methodsFor: 'accessing'!

leftTower
	^self towers at: 1!

middleTower
	^self towers at: 2!

moves
	^moves!

numberOfDisks
	^numberOfDisks!

numberOfDisks: aNaturalNumber
	"This method initializes the receiver to play
	a game using the given number of disks."

	numberOfDisks := aNaturalNumber.
	self reset.!

resetMoveCounter
	moves := 0.!

rightTower
	^self towers at: 3!

towers
	^towers!

towers: anArrayOfTowers
	towers := anArrayOfTowers.!

usedAnotherMove
	moves := moves + 1.! !

!TowersOfHanoi methodsFor: 'converting'!

indexOf: aTower
	"Return the index of aTower in the towers array.
	This is needed by my view to position towers in
	the proper part of the display.  If the index is zero
	then return an error."

	| index |

	index := self towers indexOf: aTower.
	index = 0 ifTrue: [self error: 'Unknown tower.'].
	^index!

optimalNumberOfMoves
	"The TowersOfHanoi game can always be completed
	in (2**N)-1 moves where N is the number of disks."

	^(2 raisedToInteger: self numberOfDisks) - 1! !

!TowersOfHanoi methodsFor: 'initialize-release'!

initialize
	self towers: (Array new: 3).
	1 to: self towers size do: [:k |
		self towers at: k put: Tower new].!

reset
	self leftTower loadDisks: self numberOfDisks.
	self middleTower makeEmpty.
	self rightTower makeEmpty.
	self resetMoveCounter.
	self changed: #reset.! !

!TowersOfHanoi methodsFor: 'moving'!

moveDiskFrom: source to: destination
	"This is the primitive disk moving method.  A disk
	is removed from the source to the destination disk.
	The method returns false if the operation fails and
	true if it succeeds.   The method also requests an
	update in any view that has the receiver as a model."

	| movement |

	source isEmpty ifTrue: [^false].

	(destination willAccept: source topDisk) ifFalse: [^false].

	movement := Array with: source with: destination.
	self changed: #move with: movement.
	destination addDisk: source removeDisk.
	self usedAnotherMove.

	^true!

moveDisks: count from: source to: dest using: temp
	count > 0 ifTrue: [
		self moveDisks: (count-1) from: source to: temp using: dest.
		self moveDiskFrom: source to: dest.
		self moveDisks: (count-1) from: temp to: dest using: source.
	].! !

!TowersOfHanoi methodsFor: 'playing'!

autoPlay
	self reset.
	self moveDisks: self numberOfDisks
		from: self leftTower
		to: self rightTower
		using: self middleTower.! !

!TowersOfHanoi methodsFor: 'testing'!

finished
	^self rightTower size = self numberOfDisks! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TowersOfHanoi class
	instanceVariableNames: ''!


!TowersOfHanoi class methodsFor: 'constants'!

maxNumberOfDisks
	^10! !

!TowersOfHanoi class methodsFor: 'instance creation'!

new
	^super new initialize!

open
	"Create a new game and open a window onto it."

	"TowersOfHanoi open"

	| topView game myView extent |

	topView := StandardSystemView new label: 'Towers of Hanoi'.
	topView borderWidth: 2.

	game := self usingDisks: 4.
	myView := TowersOfHanoiView new model: game.
	topView addSubView: myView.
	extent := topView viewport extent.
	topView minimumSize: extent.
	topView maximumSize: extent.
	topView controller open.!

usingDisks: count
	| numberOfDisks |

	numberOfDisks := (count max: 1) min: self maxNumberOfDisks.
	^self new numberOfDisks: numberOfDisks! !

Object subclass: #Tower
	instanceVariableNames: 'disks '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tower-of-Hanoi'!
Tower comment:
'My instances represent the towers used in a Towers of Hanoi game.   Each tower can hold zero of more Disks subject to the constraint that a larger disk cannot be placed on top of a smaller one.'!


!Tower methodsFor: 'accessing'!

disks
	^disks!

disks: aStackOfDisks
	disks := aStackOfDisks.!

size
	"How many disks are on the receive?"

	^self disks size! !

!Tower methodsFor: 'disc operations'!

addDisk: aDisk
	"If it is valid to do so, place aDisk on the top of the receiver
	otherwise report an error."

	(self willAccept: aDisk) ifFalse: [
		self error: 'Larger disks cannot be placed on smaller ones.'].

	self disks addFirst: aDisk.!

loadDisks: numberOfDisks
	"Initialize the receiver with the given number of
	disks.  The disks are guaranteed to be in the proper
	order."

	self initialize.
	numberOfDisks to: 1 by: -1 do: [:size |
		self addDisk: (Disk ofSize: size)].!

makeEmpty
	"This method clears out the receiver's old disks if
	it has any and resets the stack of disks to be empty."

	self disks isNil ifFalse: [self release].
	self initialize.!

removeDisk 
	"Remove the top-most disk from the receiver and return
	it as the result of the method.  If there are no disks on
	the receiver then return nil."

	self isEmpty ifTrue: [^nil].
	^self disks removeFirst!

topDisk 
	"Return the top-most disk of the receiver if there is
	one and nil otherwise.   If the receiver is empty, return
	nil.   This operation does not affect the receiver."

	self isEmpty ifTrue: [^nil].
	^self disks first! !

!Tower methodsFor: 'initialize-release'!

initialize
	self disks: OrderedCollection new.!

release
	self disks do: [:disk | disk release].
	self disks release.
	disks := nil.! !

!Tower methodsFor: 'testing'!

isEmpty
	"Are there any disks on the receiver tower?"

	^self size = 0!

willAccept: aDisk
	"Is it legal to place aDisk on the receiver?  It is only legal
	if the receiver is empty or its topDisk is larger than aDisk."

	^self isEmpty or: [self topDisk > aDisk]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Tower class
	instanceVariableNames: ''!


!Tower class methodsFor: 'instance creation'!

new
	^super new initialize! !

View subclass: #TowersOfHanoiView
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Tower-of-Hanoi'!
TowersOfHanoiView comment:
'My instances provide a graphical display of the state of a TowersOfHanoi game.   When a disk is moved, its graphical representation will be moved using a simple graphical animation. '!


!TowersOfHanoiView methodsFor: 'accessing'!

baseLine
	"Return the Y ordinate of the base of the towers."

	^self insetDisplayBox bottom - 20.!

diskScale
	"The displayed width of a disk is computed from its
	actual size by multiplying it by this scaling factor."

	^self class maxDiskWidth / self model numberOfDisks!

xPositionOfLeftTower
	^self xPositionOfTower: self model leftTower!

xPositionOfMiddleTower
	^self xPositionOfTower: self model middleTower!

xPositionOfRightTower
	^self xPositionOfTower: self model rightTower!

xPositionOfTower: aTower
	"This method returns the X-ordinate for the given tower.
	This is expressed in display coordinates and denotes the centre
	line of the tower."

	| middle offset index |

	index := self model indexOf: aTower.
	middle := self insetDisplayBox center x.
	index = 2 ifTrue: ["Middle" ^middle].
	offset := self class towerWidth + 20.
	^index = 1 
		ifTrue: ["Left" middle - offset]
		ifFalse: ["Right" middle + offset]! !

!TowersOfHanoiView methodsFor: 'controller access'!

defaultControllerClass
	^TowersOfHanoiController! !

!TowersOfHanoiView methodsFor: 'displaying'!

animateFrom: source to: dest
	"This method animates the movement of the disk currently 
	on the top of the source tower to its new position on top
	of the dest tower."

	| x1 x2 y1 y2 trajectory diskWidth image delay diskBox |

	diskWidth := source topDisk size * self diskScale.

	"The point x1@y1 is the top-left corner of the disk that is
	about to be moved.   The point x2@y2 is the  position where
	that disk will end up."

	x1 := (self xPositionOfTower: source) - (diskWidth // 2).
	x2 := (self xPositionOfTower: dest) - (diskWidth // 2).
 
	y1 := self baseLine - (source size * self class diskHeight) - ((source size-1) * self class gap).
	y2 := self baseLine - ((dest size+1) * self class diskHeight) - (dest size * self class gap).

	"Compute a Manhattan path between these two points.  
	To animate the movement, the method will display the disk
	at each point for a short period of time (the delay)."

	trajectory := self trajectoryFrom: x1@y1 to: x2@y2.
	delay := Delay forMilliseconds: 50.

	"Get the image of the disk that is to be moved."
	diskBox := x1@y1 extent: (diskWidth @ self class diskHeight).
	image := Form fromDisplay: diskBox.

	"Erase that disk's old image on the source tower."
	Display white: diskBox.

	"Animate the movement."
	image follow: [trajectory next] while: [delay wait.  trajectory atEnd not].

	"Display the disk in its new position."
	image displayAt: x2@y2.!

displayTower: aTower atX: xOrdinate
	| y |

	y := self baseLine - self class diskHeight.
	aTower disks reverseDo: [:disc |
		| x box width |

		width := (self diskScale * disc size) rounded.
		x := xOrdinate - (width // 2).
		box := x@y extent: width@self class diskHeight.
		Display black: box.
		y := y - self class diskHeight - 5.
	].!

displayView
	self clearInside.
	self displayTower: self model leftTower atX: self xPositionOfLeftTower.
	self displayTower: self model middleTower atX: self xPositionOfMiddleTower.
	self displayTower: self model rightTower atX: self xPositionOfRightTower.!

insideColor
	^Form white! !

!TowersOfHanoiView methodsFor: 'window access'!

defaultWindow
	| height width |

	height := self model numberOfDisks * self class diskHeight.
	width := self model towers size * self class towerWidth.
	width := width + (2 * self class xMargin).
	height := height + (2 * self class yMargin).
	^0@0 extent: width@height! !

!TowersOfHanoiView methodsFor: 'private'!

trajectoryFrom: aPoint to: bPoint
	"This method returns a ReadStream over a collection
	of points.  These points describe a Manhattan path 
	from aPoint to bPoint using three stages:  up, along,
	down.   The number of points is controlled by the 
	'intervals' class method."

	| yMin trajectory delta y x |

	yMin := self insetDisplayBox top + 10.
	trajectory := OrderedCollection new: (self class intervals * 3).
 
	delta := (aPoint y - yMin) // self class intervals.
	y := aPoint y.
	self class intervals timesRepeat: [
		y := y - delta.
		trajectory add: (aPoint x @ y).
	].

	delta := (bPoint x - aPoint x) // self class intervals.
	x := aPoint x.
	self class intervals timesRepeat: [
		x := x + delta.
		trajectory add: (x@yMin).
	].

	delta := (bPoint y - yMin) // self class intervals.
	y := yMin.
	self class intervals timesRepeat: [
		y := y + delta.
		trajectory add: (bPoint x @ y).
	].

	^ReadStream on: trajectory! !

!TowersOfHanoiView methodsFor: 'updating'!

update: aspect with: movement
	"The receiver only recognises two changed messages.
	The first is #reset which causes the entire display to be
	redrawn.  The other is #move which takes an array as
	its argument.  The first element in the movement array
	gives the source tower, the last element the destination."

	| source destination |

	aspect == #reset ifTrue: [^self displayView].
	aspect == #move ifFalse: [^self].
	source := movement first.
	destination := movement last.
	self animateFrom: source to: destination.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TowersOfHanoiView class
	instanceVariableNames: ''!


!TowersOfHanoiView class methodsFor: 'constants'!

diskHeight
	^20!

gap
	"Return the number of pixels that separate the
	disks in the Y-dimension."

	^5!

intervals
	"How many steps should each animation
	stage be divided into?"

	^10!

maxDiskWidth
	^100!

towerWidth
	^120!

xMargin
	^50!

yMargin
	^50! !


-----------------------------------------   C U T    H E R E   ------------------


-- 
Email:   kww@uk.ac.glasgow.cs  (JANET)
	 kww%cs.glasgow.ac.uk@nsfnet-relay.ac.uk  (INTERNET)
Address: Dept. of Computing Science,  University of Glasgow,
	 17 Lilybank Gardens,  Glasgow,  United Kingdom.  G12 8QQ