[Seaside] Seaslides

Romain Robbes romain.robbes at lu.unisi.ch
Fri Mar 18 16:47:06 CET 2005


	Hi Ian,





On Mar 18, 2005, at 3:52 PM, Ian Prince wrote:

>> On Mar 18, 2005, at 2:29 PM, stephane ducasse wrote:
>>
>>> romain could we get the code of the tic tac toe?
>
> On Fri, Mar 18, 2005 at 3:09 PM +0100, Romain Robbes wrote:
>
>> Sure, here they are.
>>
>> This is the source code for the visual works version of the game.
>
> Thanks. Can someone provide a Squeak version so I can post a playable 
> copy?
>



Using my great copy-pasting skills, I was able to provide you with one 
;-).
This is not tested yet, but it should work properly, provided that I 
did not forget to
copy one method...

You should be aware that there is a bug at one point in the program
(in the commented out code), namely a call like :
currentPlayer name1

should be replaced by:
currentPlayer playerName

Take this as an opportunity to learn the debugger ;-).

Cheers,
	Romain

-------------- next part --------------
WAComponent subclass: #WATTTBoard
	instanceVariableNames: 'player board combos'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TicTacToe'!

!WATTTBoard methodsFor: 'initialization' stamp: 'rr 3/18/2005 16:36'!
initialize
	"Initialize a newly created instance. This method must answer the receiver."

	super initialize.
	player := nil.
	board := Array new: 9.
	combos := #( (1 2 3) (4 5 6) (7 8 9)
				(1 4 7) (2 5 8) (3 6 9)
				(1 5 9) (3 5 7)).
	^self! !


!WATTTBoard methodsFor: 'testing' stamp: 'rr 3/18/2005 16:38'!
hasWon
	player ifNil: [^ false].
	^ combos anySatisfy: [:combo |
			combo allSatisfy: [:cell | (board at: cell) = player]]! !

!WATTTBoard methodsFor: 'testing' stamp: 'rr 3/18/2005 16:38'!
isFull
	^ board noneSatisfy: [:cell | cell isNil]! !


!WATTTBoard methodsFor: 'accessing' stamp: 'rr 3/18/2005 16:38'!
player: anObject
	player := anObject! !


!WATTTBoard methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:37'!
renderCells: cells on: html
	| content |
	cells do: [:cell |
		content := board at: cell.
		html tableData: [
			html text: content.
			"content ifNil: [html anchorWithAction: [board at: cell put: player] text: '...']
					ifNotNil: [html text: content]"
		]]! !

!WATTTBoard methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:37'!
renderContentOn: html
	html heading: 'Board'.
	"html table: [
		html tableRow: [self renderCells: (1 to: 3) on: html];
			tableRow: [self renderCells: (4 to: 6) on: html];
			tableRow: [self renderCells: (7 to: 9) on: html]]."! !


WAComponent subclass: #WATTTPlayer
	instanceVariableNames: 'name score bored'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TicTacToe'!

!WATTTPlayer methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:34'!
renderContentOn: html
	html heading: 'Player'.
	"html text: 'name : '; text: name.
	html hr.
	html text: 'score : '; text: score.
	html hr."
	"html anchorWithAction: [bored := bored not] text: 'are you bored ?'.
	html br.
	html text: 'actually : '; text: bored"! !


!WATTTPlayer methodsFor: 'winning' stamp: 'rr 3/18/2005 16:34'!
win
	score := score + 1! !


!WATTTPlayer methodsFor: 'accessing' stamp: 'rr 3/18/2005 16:40'!
playerName
	^ name! !


!WATTTPlayer methodsFor: 'initialize-release' stamp: 'rr 3/18/2005 16:33'!
initialize
	"Initialize a newly created instance. This method must answer the receiver."

	super initialize.
	name := 'no name'.
	score := 0.
	bored := false.
	^self! !

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

WATTTPlayer class
	instanceVariableNames: ''!

!WATTTPlayer class methodsFor: 'instance creation' stamp: 'rr 3/18/2005 16:35'!
named: arg1
	^self new name: arg1! !


WAComponent subclass: #WATicTacToe
	instanceVariableNames: 'p1 p2 board currentPlayer'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TicTacToe'!

!WATicTacToe methodsFor: 'initialization' stamp: 'rr 3/18/2005 16:39'!
initialize
	"Initialize a newly created instance. This method must answer the receiver."

	super initialize.
	board := WATTTBoard new.
	^self! !


!WATicTacToe methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:40'!
children
	^ Array with: p1 with: p2 with: board! !

!WATicTacToe methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:40'!
nextTurn
	board hasWon ifTrue: [self answer: currentPlayer].
	board isFull ifTrue: [self answer: nil].
	currentPlayer := currentPlayer ifNil: [p1]
								ifNotNil: [currentPlayer = p1 ifTrue: [p2] ifFalse: [p1]].
	board player: currentPlayer playerName.! !

!WATicTacToe methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:41'!
renderContentOn: html
	
	html heading: 'probably the best tic tac toe in the world'.
	html heading: 'under construction...'
	"html anchorWithAction: [self answer: p1] text: 'first player wins!!."
	"self nextTurn.
	html table: [html tableRowWith: [html render: p1] with: [html render: board] with: [html render: p2] ]"! !

!WATicTacToe methodsFor: 'rendering' stamp: 'rr 3/18/2005 16:41'!
style 
^ 'table {border: 1px solid black; background-color: lightgray} 
td {border: 1px solid black; padding: 15px} '! !


!WATicTacToe methodsFor: 'accessing' stamp: 'rr 3/18/2005 16:42'!
p1: aPlayer
	p1 := aPlayer! !

!WATicTacToe methodsFor: 'accessing' stamp: 'rr 3/18/2005 16:42'!
p2: aPlayer
	p2 := aPlayer! !

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

WATicTacToe class
	instanceVariableNames: ''!

!WATicTacToe class methodsFor: 'instance creation' stamp: 'rr 3/18/2005 16:42'!
player: arg1 playsWith: arg2

	^(self new) p1: arg1; p2: arg2;yourself! !


WATask subclass: #WATicTacToeTask
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'TicTacToe'!

!WATicTacToeTask methodsFor: 'as yet unclassified' stamp: 'rr 3/18/2005 16:32'!
go
	| n1 n2 p1 p2 winner swap |
	self inform: 'there is some work to do here !!'.
	"n1 := self request: 'player 1, enter you name : ' label: 'play' default: 'O'.
	n2 := self request: 'player 2, enter your name :' label: 'play' default: 'X'.
	p1 := WATTTPlayer named: n1.
	p2 := WATTTPlayer named: n2."
	"self call: (WATicTacToe player: p1 playsWith: p2). "
	"[true] whileTrue: [
		winner := self call: (WATicTacToe player: p1 playsWith: p2).
		winner ifNil: [self inform: 'this was a draw']
				ifNotNil: [winner win. self inform: winner name1, ' won !!'].
		swap := p1.
		p1 := p2.
		p2 := swap.]"! !

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

WATicTacToeTask class
	instanceVariableNames: ''!

!WATicTacToeTask class methodsFor: 'class initialization' stamp: 'rr 3/18/2005 16:43'!
canBeRoot
	^ true! !

!WATicTacToeTask class methodsFor: 'class initialization' stamp: 'rr 3/18/2005 16:43'!
initialize
	self registerAsApplication: 'tictactoe'! !

WATicTacToeTask initialize!
-------------- next part --------------




> Thanks,
>
> Ian.
>
>
> _______________________________________________
> Seaside mailing list
> Seaside at lists.squeakfoundation.org
> http://lists.squeakfoundation.org/listinfo/seaside
>


More information about the Seaside mailing list