[Seaside] Seaslides

David Shaffer cdshaffer at acm.org
Sat Mar 19 14:33:13 CET 2005


Ian Prince wrote:

>Chess would be great, but at the speed I play chess (and write
>code...) I'd have to set the session timeout pretty high. It would be
>annoying to reach the end game and get a "That page has expired. You
>are being redirected to /seaside/chess".
>
>Ian.
>  
>
Here's a start...I could resist.  It needs a lot of work but you can 
basically play chess.  It was too easy...

David

-------------- next part --------------
WATask subclass: #ChessTask
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SCChess'!

!ChessTask methodsFor: 'rendering' stamp: 'cds 3/19/2005 12:26'!
go
	| player1 player2 |
	player1 := self makePlayer.
	player2 := self makePlayer.
	player1 opponent: player1.
	player2 opponent: player2.
	self call: (ChessView player1: player1 player2: player2)
	! !

!ChessTask methodsFor: 'rendering' stamp: 'cds 3/19/2005 12:26'!
makePlayer
	^ChessPlayer new initialize! !

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

ChessTask class
	instanceVariableNames: ''!

!ChessTask class methodsFor: 'seaside' stamp: 'cds 3/19/2005 12:12'!
canBeRoot
	^true! !


WAComponent subclass: #ChessView
	instanceVariableNames: 'player1 player2 board history redoList boardPieces moveInProgress startPosition'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'SCChess'!

!ChessView methodsFor: 'user actions' stamp: 'cds 3/19/2005 13:22'!
spaceSelectedRow: row col: col
	moveInProgress 
		ifFalse: [moveInProgress := true.
			startPosition := (self squareForRow: row col: col)]
		ifTrue: [moveInProgress := false.
			self movePieceFrom: startPosition to: (self squareForRow: row col: col)]! !


!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 12:49'!
classForRow: row col: col
	^row + col \\ 2 = 0
		ifTrue: ['black']
		ifFalse: ['white']! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 13:09'!
renderBoardOn: html 
	html table: 
			[1 to: 8
				do: 
					[:row | 
					html tableRow: 
							[1 to: 8
								do: 
									[:col | 
									html
										attributeAt: 'width' put: 50;
										attributeAt: 'height' put: 50.
									html tableData: 
											[html divClass: (self classForRow: row col: col)
												with: 
													[self 
														renderPieceAtRow: row
														col: col
														on: html]]]]]]! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 12:22'!
renderContentOn: html
	self renderPlayerInfoOn: html.
	self renderBoardOn: html.
! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 13:14'!
renderEmptySpaceRow: row col: col on: html 
	^moveInProgress
		ifTrue: [html anchorWithAction: [self spaceSelectedRow: row col: col] text: [html space]]
		ifFalse: [html space]! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 13:10'!
renderPieceAtRow: row col: col on: html 
	| piece selector image index |
	piece := (boardPieces at: row) at: col.
	piece ifNil: 
			[^self 
				renderEmptySpaceRow: row
				col: col
				on: html].
	index := piece key.
	piece value ifFalse: [index := index + 6].
	selector := #(#whitePawnImage #whiteKnightImage #whiteBishopImage #whiteRookImage #whiteQueenImage #whiteKingImage #blackPawnImage #blackKnightImage #blackBishopImage #blackRookImage #blackQueenImage #blackKingImage) 
				at: index.
	image := ChessMorph perform: selector.
	html anchorWithAction: [self spaceSelectedRow: row col: col] image: image! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 12:22'!
renderPlayerInfoOn: html! !

!ChessView methodsFor: 'rendering' stamp: 'cds 3/19/2005 13:08'!
style
	^'div.black { background-color: grey; }
	div.white {background-color: white; }'! !


!ChessView methodsFor: 'initialization' stamp: 'cds 3/19/2005 12:31'!
initializeBoardPieces
	boardPieces := Array new: 8.
	1 to: 8 do: [:row |
		boardPieces at: row put: (Array new: 8)]! !

!ChessView methodsFor: 'initialization' stamp: 'cds 3/19/2005 13:14'!
newGame
	board ifNil:[board _ ChessBoard new].
	board initialize.
	board userAgent: self.
	self initializeBoardPieces.
	board initializeNewBoard.
	history := OrderedCollection new.
	redoList := OrderedCollection new.
	moveInProgress := false! !

!ChessView methodsFor: 'initialization' stamp: 'cds 3/19/2005 12:15'!
player1: p1 player2: p2
	player1 := p1.
	player2 := p2.
	self newGame! !


!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 13:23'!
addedPiece: piece at: square white: isWhite 
	self boardPieceAt: square put: piece -> isWhite
! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 13:21'!
completedMove: aMove white: isWhitePlayer! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 12:27'!
gameReset! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 13:29'!
movePieceFrom: sourceSquare to: destSquare
	| move |
	board ifNil:[^self].
	board movePieceFrom: sourceSquare to: destSquare.
	board activePlayer = board whitePlayer ifFalse: [move := board searchAgent think.
		board movePieceFrom: move sourceSquare 
					to: move destinationSquare].! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 13:20'!
movedPiece: piece from: sourceSquare to: destSquare
	| oldPiece |
	oldPiece := self boardPieceAt: sourceSquare.
	self boardPieceAt: sourceSquare put: nil.
	self boardPieceAt: destSquare put: oldPiece! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 13:30'!
removedPiece: piece at: position
	self boardPieceAt: position put: nil! !

!ChessView methodsFor: 'chess user agent' stamp: 'cds 3/19/2005 12:58'!
squareForRow: row col: col
	^(row - 1) * 8 + col! !


!ChessView methodsFor: 'private' stamp: 'cds 3/19/2005 13:21'!
boardPieceAt: position
	^(boardPieces at: (self rowForSquare: position)) at: (self colForSquare: position)! !

!ChessView methodsFor: 'private' stamp: 'cds 3/19/2005 13:21'!
boardPieceAt: position put: aPiece
	^(boardPieces at: (self rowForSquare: position)) at: (self colForSquare: position) put: aPiece! !

!ChessView methodsFor: 'private' stamp: 'cds 3/19/2005 12:58'!
colForSquare: square 
	^(square - 1) \\ 8 + 1! !

!ChessView methodsFor: 'private' stamp: 'cds 3/19/2005 12:58'!
rowForSquare: square 
	^(square - 1) // 8 + 1! !

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

ChessView class
	instanceVariableNames: ''!

!ChessView class methodsFor: 'instance creation' stamp: 'cds 3/19/2005 12:14'!
player1: player1 player2: player2
	^self new player1: player1 player2: player2; yourself! !


More information about the Seaside mailing list