The Trunk: EToys-mt.395.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: EToys-mt.395.mcz

commits-2
Marcel Taeumel uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-mt.395.mcz

==================== Summary ====================

Name: EToys-mt.395
Author: mt
Time: 3 June 2020, 3:24:51.881117 pm
UUID: b4c7142d-c357-3448-86fd-62a029de049d
Ancestors: EToys-mt.394

Fixes for the original chess game. Adds the revised version, Chess 960, to Etoys games catalogue. Also available through the parts bin. Thanks to Stéphane (spfa)!

Bugfixes:

- castling was not possible when a rook was menaced
- a test for king attack in black king-side castling was missing
- the cached number of pawns is sometimes off, which could lead to a
DivideByZero error in some endgames (this is fixed, but not the
discrepancy which still effects the material evaluation)
- a pawn taken en-passant was not removed from display

One notable bug left is that undoing a castling move makes it impossible
to castle again.

Improvements:

- nicer display, scalable (with assets from wikimedia common)
- the board is now sticky and cannot be accidentally grabbed
- hints (from the 'help' button) now appear in the status line
- support for Fischer randomized chess, aka Chess960

Changes:

- to castle, one now has to move the king over the rook

=============== Diff against EToys-mt.394 ===============

Item was changed:
  SystemOrganization addCategory: #'Etoys-Buttons'!
  SystemOrganization addCategory: #'Etoys-CustomEvents'!
  SystemOrganization addCategory: #'Etoys-Experimental'!
  SystemOrganization addCategory: #'Etoys-OLPC-Display'!
  SystemOrganization addCategory: #'Etoys-Outliner'!
  SystemOrganization addCategory: #'Etoys-Protocols'!
  SystemOrganization addCategory: #'Etoys-Protocols-Type Vocabularies'!
  SystemOrganization addCategory: #'Etoys-ReleaseBuilder'!
  SystemOrganization addCategory: #'Etoys-Scripting'!
  SystemOrganization addCategory: #'Etoys-Scripting Support'!
  SystemOrganization addCategory: #'Etoys-Scripting Tiles'!
  SystemOrganization addCategory: #'Etoys-Squeakland-BroomMorphs-Base'!
  SystemOrganization addCategory: #'Etoys-Squeakland-BroomMorphs-Connectors'!
  SystemOrganization addCategory: #'Etoys-Squeakland-EToys-Kedama'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Buttons'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Calendar'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Debugger'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Help'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Input'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting Support'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Scripting Tiles'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-SpeechBubbles'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Etoys-Tile Scriptors'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Graphics-Text'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Graphics-Tools-Intersection'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Graphics-Tools-Simplification'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Graphics-Tools-Triangulation'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Basic'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Books'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Components'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Demo'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Experimental'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Games'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Games-Chess'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-GeeMail'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Kernel'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Mentoring'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Navigators'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-PDA'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-PartsBin'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Support'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Widgets'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Windows'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Worlds'!
  SystemOrganization addCategory: #'Etoys-Squeakland-MorphicExtras-AdditionalMorphs'!
  SystemOrganization addCategory: #'Etoys-Squeakland-MorphicExtras-Charts'!
  SystemOrganization addCategory: #'Etoys-Squeakland-MorphicExtras-Postscript Filters'!
  SystemOrganization addCategory: #'Etoys-Squeakland-MorphicExtras-WebCam'!
  SystemOrganization addCategory: #'Etoys-Squeakland-MorphicExtras-Widgets'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Multilingual-Languages'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Multilingual-TextConversion'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-HTML-Formatter'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-HTML-Forms'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-HTML-Parser'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-HTML-Parser Entities'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-HTML-Tokenizer'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-MIME'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-TelNet WordNet'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-UI'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Network-Url'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Protocols-Type Vocabularies'!
  SystemOrganization addCategory: #'Etoys-Squeakland-SISS-Serialization'!
  SystemOrganization addCategory: #'Etoys-Squeakland-ST80-Morphic'!
  SystemOrganization addCategory: #'Etoys-Squeakland-SUnit'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Interface'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Ogg'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Sound-Scores'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Sugar'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Support'!
  SystemOrganization addCategory: #'Etoys-Squeakland-System-Clipboard-Extended'!
  SystemOrganization addCategory: #'Etoys-Squeakland-System-Compiler'!
  SystemOrganization addCategory: #'Etoys-Squeakland-System-Exceptions Kernel'!
  SystemOrganization addCategory: #'Etoys-Squeakland-System-Support'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Changes'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Explorer'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tools-Process Browser'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tweak-Kedama-ObjectVectors'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tweak-Kedama-ParseTree-AttributeDefinition'!
  SystemOrganization addCategory: #'Etoys-Squeakland-Tweak-Kedama-ParseTreeTransformer'!
  SystemOrganization addCategory: #'Etoys-Stacks'!
  SystemOrganization addCategory: #'Etoys-StarSqueak'!
  SystemOrganization addCategory: #'Etoys-Support'!
  SystemOrganization addCategory: #'Etoys-Tests'!
  SystemOrganization addCategory: #'Etoys-Tile Scriptors'!
  SystemOrganization addCategory: #'Etoys-UserInterfaceTheme'!
  SystemOrganization addCategory: #'Etoys-Widgets'!
+ SystemOrganization addCategory: #'Etoys-Squeakland-Morphic-Games-Chess960'!

Item was added:
+ ChessBoard subclass: #Chess960Board
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !Chess960Board commentStamp: 'spfa 6/2/2020 15:13' prior: 0!
+ Chess960Board can handle Fisher-style random starting positions in home ranks!

Item was added:
+ ----- Method: Chess960Board>>initialize (in category 'initialize') -----
+ initialize
+ generator ifNil:[generator := Chess960MoveGenerator new initialize].
+ searchAgent ifNil:[searchAgent := ChessPlayerAI new initialize].
+ self resetGame.
+ !

Item was added:
+ ----- Method: Chess960Board>>initializeNewBoard (in category 'initialize') -----
+ initializeNewBoard
+
+ | conf |
+
+ self resetGame.
+ conf := Chess960Configuration new.
+ whitePlayer addWhitePieces: conf.
+ blackPlayer addBlackPieces: conf.
+ !

Item was added:
+ ----- Method: Chess960Board>>resetGame (in category 'initialize') -----
+ resetGame
+ hashKey := hashLock := 0.
+ whitePlayer := Chess960Player new initialize.
+ blackPlayer := Chess960Player new initialize.
+ whitePlayer opponent: blackPlayer.
+ whitePlayer board: self.
+ blackPlayer opponent: whitePlayer.
+ blackPlayer board: self.
+ activePlayer := whitePlayer.
+ searchAgent reset: self.
+ userAgent ifNotNil:[userAgent gameReset].!

Item was added:
+ Object subclass: #Chess960Configuration
+ instanceVariableNames: 'positions king leftRook rightRook'
+ classVariableNames: ''
+ poolDictionaries: 'ChessConstants'
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !Chess960Configuration commentStamp: 'spfa 6/2/2020 15:13' prior: 0!
+ A Chess960Configuration is a Fisher-style random starting arrangement of pieces in the home ranks!

Item was added:
+ ----- Method: Chess960Configuration class>>new (in category 'as yet unclassified') -----
+ new
+
+ | rand positions k |
+
+ rand := Random new.
+ positions := Array new: 8.
+ positions at: (rand nextInt: 4) * 2 - 1 put: Bishop.
+ positions at: (rand nextInt: 4) * 2 put: Bishop.
+ positions at: (k := (((1 to: 8) select: [:n | (positions at: n) isNil]) copyFrom: 2 to: 5) atRandom: rand) put: King.
+ positions at: (((1 to: k-1) select: [:n | (positions at: n) isNil]) atRandom: rand) put: Rook.
+ positions at: (((k+1 to: 8) select: [:n | (positions at: n) isNil]) atRandom: rand) put: Rook.
+ positions at: (((1 to: 8) select: [:n | (positions at: n) isNil]) atRandom: rand) put: Queen.
+ positions at: ((1 to: 8) detect: [:n | (positions at: n) isNil]) put: Knight.
+ positions at: ((1 to: 8) detect: [:n | (positions at: n) isNil]) put: Knight.
+
+ ^ self basicNew positions: positions
+ !

Item was added:
+ ----- Method: Chess960Configuration>>initialKingPosition (in category 'positions') -----
+ initialKingPosition
+
+ ^ king ifNil: [king := positions indexOf: King]!

Item was added:
+ ----- Method: Chess960Configuration>>initialLeftRookPosition (in category 'positions') -----
+ initialLeftRookPosition
+
+ ^ leftRook ifNil: [leftRook := positions indexOf: Rook]!

Item was added:
+ ----- Method: Chess960Configuration>>initialRightRookPosition (in category 'positions') -----
+ initialRightRookPosition
+
+ ^ rightRook ifNil: [rightRook := positions indexOf: Rook startingAt: self initialKingPosition]!

Item was added:
+ ----- Method: Chess960Configuration>>positions (in category 'positions') -----
+ positions
+
+ ^ positions!

Item was added:
+ ----- Method: Chess960Configuration>>positions: (in category 'positions') -----
+ positions: anArray
+
+ positions := anArray.
+ king := leftRook := rightRook := nil!

Item was added:
+ ChessMorph subclass: #Chess960Morph
+ instanceVariableNames: 'images message squareSize'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !Chess960Morph commentStamp: 'spfa 6/2/2020 15:10' prior: 0!
+ Chess960Morph is a nicer, scalable, skin for ChessMorph.
+ It also can play Fischer random chess (use the '960' button)
+
+ Chess960Morph new openInWorld
+
+ (Chess960Morph new squareSize: 100) openInWorld
+ !

Item was added:
+ ----- Method: Chess960Morph class>>descriptionForPartsBin (in category 'parts bin') -----
+ descriptionForPartsBin
+ ^ self partName: 'Chess 960' translatedNoop
+ categories: {'Games' translatedNoop}
+ documentation: 'A fine game of chess. Revised by Stéphane Rollandin (spfa).' translatedNoop!

Item was added:
+ ----- Method: Chess960Morph>>addButtonRow (in category 'initialize') -----
+ addButtonRow
+
+ | r m |
+ r := AlignmentMorph newRow hResizing: #shrinkWrap; vResizing: #shrinkWrap; color: Color transparent.
+ r cellInset: 2.
+ r addMorphBack: (self buttonName: '  New  ' translated action: #newGame).
+ r addMorphBack: (self buttonName: '  960  ' translated action: #new960Game).
+ r addMorphBack: (self buttonName: '  Help  ' translated action: #findBestMove).
+ r addMorphBack: (self buttonName: '  Play  ' translated action: #thinkAndMove).
+ r addMorphBack: (self buttonName: '  Auto  ' translated action: #autoPlay).
+ r addMorphBack: (self buttonName: '  Undo  ' translated action: #undoMove).
+ r addMorphBack: (self buttonName: '  Redo  ' translated action: #redoMove).
+ r addMorphBack: (self buttonName: '  Quit  ' translated action: #delete).
+ r disableTableLayout: true.
+ r align: r bounds topLeft with: self layoutBounds topLeft.
+ self addMorphFront: r.
+ m := UpdatingStringMorph on: self selector: #statusString.
+ m useStringFormat.
+ m disableTableLayout: true.
+ m stepTime: 50.
+ m align: m bounds topLeft with: r fullBounds bottomLeft.
+ self addMorphFront: m.
+ m
+ font: self textFont;
+ color: self statusColor;
+ maximumWidth: self width - self squareSize;
+ position:  self position + (self squareSize @ self squareSize * 0.6)!

Item was added:
+ ----- Method: Chess960Morph>>addSquares (in category 'initialize') -----
+ addSquares
+ | white black border square index |
+ white := self whiteColor.
+ black := self blackColor.
+ border := self highColor.
+ index := 0.
+ #(
+ ( ' ' 'a' 'b' 'c' 'd' 'e' 'f' 'g' 'h' ' ')
+ ( '1' 'B' 'W' 'B' 'W' 'B' 'W' 'B' 'W' ' ')
+ ( '2' 'W' 'B' 'W' 'B' 'W' 'B' 'W' 'B' ' ')
+ ( '3' 'B' 'W' 'B' 'W' 'B' 'W' 'B' 'W' ' ')
+ ( '4' 'W' 'B' 'W' 'B' 'W' 'B' 'W' 'B' ' ')
+ ( '5' 'B' 'W' 'B' 'W' 'B' 'W' 'B' 'W' ' ')
+ ( '6' 'W' 'B' 'W' 'B' 'W' 'B' 'W' 'B' ' ')
+ ( '7' 'B' 'W' 'B' 'W' 'B' 'W' 'B' 'W' ' ')
+ ( '8' 'W' 'B' 'W' 'B' 'W' 'B' 'W' 'B' ' ')
+ ( ' ' ' ' ' ' ' ' ' ' ' ' ' ' ' ' ' ' ' ')
+ ) do:[:file|
+ file do:[:sq|
+ square := self newSquare.
+ square borderWidth: 0.
+ (sq = 'W' or:[sq = 'B']) ifTrue:[
+ square color: (sq = 'W' ifTrue:[white] ifFalse:[black]).
+ square borderColor: border.
+ square setProperty: #squarePosition toValue: (index := index + 1).
+ square setNameTo:
+ (String with: ($a asInteger + (index - 1 bitAnd: 7)) asCharacter with: ($1 asInteger + (index -1 bitShift: -3)) asCharacter).
+ square on: #mouseEnter send: #showMoves:from: to: self.
+ square on: #mouseEnterDragging send: #dragSquareEnter:from: to: self.
+ square on: #mouseLeaveDragging send: #dragSquareLeave:from: to: self.
+ ] ifFalse:["decoration"
+ square color: Color transparent.
+ sq = ' ' ifFalse:[
+ square addMorph: ((StringMorph contents: sq font: self textFont)
+ color: self labelsColor).
+ ].
+ ].
+ square extent: self squareSize @ self squareSize.
+ self addMorphBack: square.
+ square submorphs ifNotEmpty: [square submorphs first center: square center]
+ ]].
+ !

Item was added:
+ ----- Method: Chess960Morph>>blackColor (in category 'theme') -----
+ blackColor
+
+ " Color earth paler duller."
+ "^ Color grass duller"
+ ^ Color r: 0.343 g: 0.576 b: 0.207!

Item was added:
+ ----- Method: Chess960Morph>>buttonColor (in category 'theme') -----
+ buttonColor
+
+ " ^ Color lightBlue3 whiter "
+ ^ Color r: 0.667 g: 0.792 b: 0.833!

Item was added:
+ ----- Method: Chess960Morph>>buttonName:action: (in category 'initialize') -----
+ buttonName: aString action: aSymbol
+
+ ^ SimpleButtonMorph new
+ target: self;
+ label: aString;
+ actionSelector: aSymbol;
+ color: self buttonColor;
+ borderWidth: 1;
+ borderRaised.
+ !

Item was added:
+ ----- Method: Chess960Morph>>defaultBounds (in category 'initialization') -----
+ defaultBounds
+ "answer the default bounds for the receiver"
+ ^ 0 @ 0 corner: (self squareSize * 10 + 10) @ (self squareSize * 10 + 10)!

Item was added:
+ ----- Method: Chess960Morph>>defaultColor (in category 'theme') -----
+ defaultColor
+
+ "^ Color paleTeal duller duller"
+ ^ Color r: 0.467 g: 0.631 b: 0.71!

Item was added:
+ ----- Method: Chess960Morph>>findBestMove (in category 'playing') -----
+ findBestMove
+ | move |
+ board ifNil: [^ self].
+ board searchAgent isThinking ifTrue:[^self].
+
+ "tmp - board should be nil when the game is over"
+ ((1 to: 64) allSatisfy: [:n |
+ (board activePlayer pieces at: n) isZero
+ or: [(board activePlayer findValidMovesAt: n) isEmpty]])
+ ifTrue: [message := (board activePlayer isWhitePlayer
+ ifTrue: ['white'] ifFalse: ['black']), ' lost'.
+ ^ self].
+
+ Cursor wait showWhile:[move := board searchAgent think].
+ message :=  'I suggest ' translated, move moveString.
+ ^move
+ !

Item was added:
+ ----- Method: Chess960Morph>>finishedGame: (in category 'as yet unclassified') -----
+ finishedGame: result
+
+ super finishedGame: result.
+ message := #('black won' 'draw' 'white won') at: result * 2 + 1!

Item was added:
+ ----- Method: Chess960Morph>>highColor (in category 'theme') -----
+ highColor
+
+ " ^ Color lightGold"
+ ^ Color r: 0.992 g: 0.863 b: 0.361!

Item was added:
+ ----- Method: Chess960Morph>>images (in category 'theme') -----
+ images
+
+ ^ images ifNil: [images := ChessPieceMorphWC piecesWithHeight: self squareSize - 5]!

Item was added:
+ ----- Method: Chess960Morph>>initialize (in category 'initialization') -----
+ initialize
+ "initialize the state of the receiver"
+ super initialize.
+ self bounds: self defaultBounds.
+ self beSticky!

Item was added:
+ ----- Method: Chess960Morph>>labelsColor (in category 'theme') -----
+ labelsColor
+
+ " ^ Color armyGreen"
+ ^ Color r: 0.294 g: 0.365 b: 0.086!

Item was added:
+ ----- Method: Chess960Morph>>movedPiece:from:to: (in category 'game callbacks') -----
+ movedPiece: piece from: sourceSquare to: destSquare
+ | sourceMorph destMorph sourcePos destPos w startTime nowTime deltaTime |
+ sourceMorph := (self atSquare: sourceSquare) firstSubmorph.
+ destMorph := self atSquare: destSquare.
+ animateMove ifTrue:[
+ sourcePos := sourceMorph boundsInWorld center.
+ destPos := destMorph boundsInWorld center.
+ (w := self world) ifNotNil:[
+ w addMorphFront: sourceMorph.
+ deltaTime := (sourcePos dist: destPos) * 3 asInteger.
+ startTime := Time millisecondClockValue.
+ [nowTime := Time millisecondClockValue.
+ nowTime - startTime < deltaTime] whileTrue:[
+ sourceMorph center: sourcePos + (destPos - sourcePos * (nowTime - startTime) // deltaTime) asIntegerPoint.
+ w displayWorldSafely].
+ sourceMorph removeDropShadow.
+ ].
+ ].
+ destMorph removeAllMorphs.
+ destMorph addMorphCentered: sourceMorph.
+ animateMove := false.
+ message := nil.!

Item was added:
+ ----- Method: Chess960Morph>>new960Game (in category 'initialize') -----
+ new960Game
+ board := Chess960Board new.
+ board initialize.
+ board userAgent: self.
+ board initializeNewBoard.
+ history := OrderedCollection new.
+ redoList := OrderedCollection new.
+ message := nil
+ !

Item was added:
+ ----- Method: Chess960Morph>>newPiece:white: (in category 'initialize') -----
+ newPiece: piece white: isWhite
+
+ | index selector m |
+ index := piece.
+ isWhite ifFalse:[index := index + 6].
+ selector := #(
+ whitePawn
+ whiteKnight
+ whiteBishop
+ whiteRook
+ whiteQueen
+ whiteKing
+
+ blackPawn
+ blackKnight
+ blackBishop
+ blackRook
+ blackQueen
+ blackKing) at: index.
+ m := ChessPieceMorph new image: (self images at: selector).
+ m setProperty: #isWhite toValue: isWhite.
+ m setProperty: #piece toValue: piece.
+ ^m!

Item was added:
+ ----- Method: Chess960Morph>>reinstallPieces (in category 'resizing') -----
+ reinstallPieces
+
+ board whitePlayer pieces doWithIndex: [:pc :n |
+ pc isZero ifFalse: [
+ self addedPiece: pc at: n white: true]].
+
+ board blackPlayer pieces doWithIndex: [:pc :n |
+ pc isZero ifFalse: [
+ self addedPiece: pc at: n white: false]].!

Item was added:
+ ----- Method: Chess960Morph>>setExtentFromHalo: (in category 'miscellaneous') -----
+ setExtentFromHalo: anExtent
+
+ self squareSize: (anExtent x - 10) //10.!

Item was added:
+ ----- Method: Chess960Morph>>showMovesAt: (in category 'events') -----
+ showMovesAt: square
+ | list |
+ board ifNil:[^self].
+ board searchAgent isThinking ifTrue:[^self].
+ self squaresDo:[:m| m borderWidth: 0].
+ list := board activePlayer findValidMovesAt: square.
+ list isEmpty ifTrue:[^self].
+ (self atSquare: square) borderWidth: 2.
+ list do:[:move|
+ (self atSquare: (move triggerSquareIn: board)) borderWidth: 5.
+ ].!

Item was added:
+ ----- Method: Chess960Morph>>squareSize (in category 'resizing') -----
+ squareSize
+
+ ^ squareSize ifNil: [70]!

Item was added:
+ ----- Method: Chess960Morph>>squareSize: (in category 'resizing') -----
+ squareSize: anInteger
+
+ | ss |
+
+ ss := anInteger max: 48.
+
+ squareSize := ss.
+ images := nil.
+ submorphs do: #delete.
+ self extent: (ss * 10 + 10) @ (ss * 10 + 10) .
+ self addSquares.
+ self addButtonRow.
+ self reinstallPieces!

Item was added:
+ ----- Method: Chess960Morph>>statusColor (in category 'theme') -----
+ statusColor
+
+ " ^ Color reallyLightBlue "
+ ^ Color r: 0.831 g: 1 b: 1!

Item was added:
+ ----- Method: Chess960Morph>>statusString (in category 'other stuff') -----
+ statusString
+
+ ^ message ifNil: [super statusString]!

Item was added:
+ ----- Method: Chess960Morph>>swappedPieceOn:withPieceOn: (in category 'game callbacks') -----
+ swappedPieceOn: aSquare withPieceOn: bSquare
+ | aMorph bMorph |
+
+ aMorph := (self atSquare: aSquare) firstSubmorph.
+ bMorph := (self atSquare: bSquare) firstSubmorph.
+
+ (self atSquare: aSquare) removeAllMorphs.
+ (self atSquare: aSquare) addMorphCentered: bMorph.
+
+ (self atSquare: bSquare)  removeAllMorphs.
+ (self atSquare: bSquare)  addMorphCentered: aMorph.
+
+ message := nil.!

Item was added:
+ ----- Method: Chess960Morph>>textFont (in category 'theme') -----
+ textFont
+
+ | ps |
+
+ ps := self squareSize < 80 ifTrue: [12] ifFalse: [15].
+
+ ^ TTCFont familyName: 'BitstreamVeraSans' pointSize: ps emphasis: 1
+ !

Item was added:
+ ----- Method: Chess960Morph>>whiteColor (in category 'theme') -----
+ whiteColor
+
+ " ^ Color ivory"
+ ^ Color r: 1 g: 1 b: 0.94!

Item was added:
+ ChessMoveGenerator subclass: #Chess960MoveGenerator
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !Chess960MoveGenerator commentStamp: 'spfa 6/1/2020 14:56' prior: 0!
+ Chess960MoveGenerator implements the specific castling checks and moves for Chess960!

Item was added:
+ ----- Method: Chess960MoveGenerator>>canCastleBlackKingSide (in category 'support') -----
+ canCastleBlackKingSide
+
+ (castlingStatus bitAnd: CastlingEnableKingSide) = 0 ifFalse:[^false].
+
+ (myPlayer rightCastlingField inject: 0 into: [:sum :s|
+ sum + (myPieces at: s) + (itsPieces at: s)]) = (King + Rook)
+ ifFalse:[^false].
+
+ myPlayer rightCastlingWalk in: [:w |
+ (self checkRookMoversAttacksAlong: w) ifTrue: [^false].
+ (self checkBishopMoversAttacksAlong: w) ifTrue: [^ false].
+ (self checkKnightAttacksAlong: w) ifTrue: [^ false].
+ (self checkPawnsAttacksAlong: w) ifTrue: [^ false].
+ (self checkKingAttacksAlong: w) ifTrue: [^ false]].
+
+ (self checkAttack: (myPlayer initialKingSquare - 1 to: A8 by: -1) fromPieces: RookMovers)
+ ifTrue: [^false].
+ (self checkAttack: {H8} fromPieces: RookMovers) ifTrue: [^false].
+
+ ^true.
+
+
+
+
+ !

Item was added:
+ ----- Method: Chess960MoveGenerator>>canCastleBlackQueenSide (in category 'support') -----
+ canCastleBlackQueenSide
+
+ (castlingStatus bitAnd: CastlingEnableQueenSide) = 0 ifFalse:[^false].
+
+ (myPlayer leftCastlingField inject: 0 into: [:sum :s|
+ sum + (myPieces at: s) + (itsPieces at: s)]) = (King + Rook)
+ ifFalse:[^false].
+
+ myPlayer leftCastlingWalk in: [:w |
+ (self checkRookMoversAttacksAlong: w) ifTrue: [^false].
+ (self checkBishopMoversAttacksAlong: w) ifTrue: [^ false].
+ (self checkKnightAttacksAlong: w) ifTrue: [^ false].
+ (self checkPawnsAttacksAlong: w) ifTrue: [^ false].
+ (self checkKingAttacksAlong: w) ifTrue: [^ false]].
+
+ (self checkAttack: (myPlayer initialKingSquare +1 to: H8) fromPieces: RookMovers)
+ ifTrue: [^false].
+ (self checkAttack: {B8 . A8} fromPieces: RookMovers) ifTrue: [^false].
+
+
+ ^true.
+
+
+
+
+ !

Item was added:
+ ----- Method: Chess960MoveGenerator>>canCastleWhiteKingSide (in category 'support') -----
+ canCastleWhiteKingSide
+
+ (castlingStatus bitAnd: CastlingEnableKingSide) = 0 ifFalse:[^false].
+
+ (myPlayer rightCastlingField inject: 0 into: [:sum :s|
+ sum + (myPieces at: s) + (itsPieces at: s)]) = (King + Rook)
+ ifFalse:[^false].
+
+ myPlayer rightCastlingWalk in: [:w |
+ (self checkRookMoversAttacksAlong: w) ifTrue: [^false].
+ (self checkBishopMoversAttacksAlong: w) ifTrue: [^ false].
+ (self checkKnightAttacksAlong: w) ifTrue: [^ false].
+ (self checkPawnsAttacksAlong: w) ifTrue: [^ false].
+ (self checkKingAttacksAlong: w) ifTrue: [^ false]].
+
+ (self checkAttack: (myPlayer initialKingSquare - 1 to: A1 by: -1) fromPieces: RookMovers)
+ ifTrue: [^false].
+ (self checkAttack: {H1} fromPieces: RookMovers) ifTrue: [^false].
+
+ ^true.
+
+
+
+
+ !

Item was added:
+ ----- Method: Chess960MoveGenerator>>canCastleWhiteQueenSide (in category 'support') -----
+ canCastleWhiteQueenSide
+
+ (castlingStatus bitAnd: CastlingEnableQueenSide) = 0 ifFalse:[^false].
+
+ (myPlayer leftCastlingField inject: 0 into: [:sum :s|
+ sum + (myPieces at: s) + (itsPieces at: s)]) = (King + Rook)
+ ifFalse:[^false].
+
+ myPlayer leftCastlingWalk in: [:w |
+ (self checkRookMoversAttacksAlong: w) ifTrue: [^false].
+ (self checkBishopMoversAttacksAlong: w) ifTrue: [^ false].
+ (self checkKnightAttacksAlong: w) ifTrue: [^ false].
+ (self checkPawnsAttacksAlong: w) ifTrue: [^ false].
+ (self checkKingAttacksAlong: w) ifTrue: [^ false]].
+
+ (self checkAttack: (myPlayer initialKingSquare + 1 to: H1) fromPieces: RookMovers)
+ ifTrue: [^false].
+ (self checkAttack: {B1 . A1} fromPieces: RookMovers) ifTrue: [^false].
+
+ ^true.
+
+
+
+
+ !

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkBishopMoversAttacksAlong: (in category 'support') -----
+ checkBishopMoversAttacksAlong: anArray
+
+ "anArray contains consecutive, ordered squares that are all either in rank 8 or in rank 1"
+
+ anArray do: [:s |
+ (self checkBishopMoversAttacksOn: s) ifTrue: [^ true]].
+
+ ^ false!

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkBishopMoversAttacksOn: (in category 'support') -----
+ checkBishopMoversAttacksOn: aSquare
+
+ "aSquare is either in rank 8 or in rank 1"
+
+ | leftDiagonal rightDiagonal |
+
+ myPlayer isWhitePlayer ifFalse: [
+ leftDiagonal := (1 to: aSquare - A8) collect: [:n | aSquare - (n * 7)].
+ rightDiagonal := (1 to: H8 - aSquare) collect: [:n | aSquare - (n * 9)]
+ ]
+ ifTrue: [
+ leftDiagonal := (1 to: aSquare - A1) collect: [:n | aSquare + (n * 7)].
+ rightDiagonal := (1 to: H1 - aSquare) collect: [:n | aSquare + (n * 9)]
+ ].
+
+ ^ (self checkAttack: leftDiagonal fromPieces: BishopMovers)
+ or: [self checkAttack: rightDiagonal fromPieces: BishopMovers]!

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkKingAttacksAlong: (in category 'support') -----
+ checkKingAttacksAlong: anArray
+
+ "anArray contains consecutive, ordered squares that are all either in rank 8 or in rank 1"
+
+ | kpos |
+
+ "somewhat overkill because some positions can never be reached by opponent king"
+ kpos := Array streamContents: [:str |
+ str nextPut: anArray first - 1.
+ str nextPutAll: anArray.
+ str nextPut: anArray last + 1].
+
+ ^ self checkUnprotectedAttack:
+ (kpos + (myPlayer isWhitePlayer ifTrue: [8] ifFalse: [-8]))
+ fromPiece: King!

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkKnightAttacksAlong: (in category 'support') -----
+ checkKnightAttacksAlong: anArray
+
+ "anArray contains consecutive, ordered squares that are all either in rank 8 or in rank 1"
+
+ | kpos1 kpos2 |
+
+ "rank at distance 1"
+ kpos1 := (anArray - 2) union: (anArray + 2).
+
+ myPlayer isWhitePlayer ifTrue: [
+ kpos1 min = 0 ifTrue: [kpos1 := kpos1 copyWithout: 0].
+ kpos1 max = 9 ifTrue: [kpos1 := kpos1 copyWithout: 9]].
+
+ (self checkUnprotectedAttack:
+ (kpos1 + (myPlayer isWhitePlayer ifTrue: [8] ifFalse: [-8]))
+ fromPiece: Knight) ifTrue: [^ true].
+
+ "rank at distance 2 - same logic as for pawns at distance 1"
+ kpos2 := Array streamContents: [:str |
+ str nextPut: anArray min - 1.
+ anArray size > 1 ifTrue: [str nextPutAll: anArray].
+ str nextPut: anArray max + 1].
+
+ ^ self checkUnprotectedAttack:
+ (kpos2 + (myPlayer isWhitePlayer ifTrue: [16] ifFalse: [-16]))
+ fromPiece: Knight!

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkPawnsAttacksAlong: (in category 'support') -----
+ checkPawnsAttacksAlong: anArray
+
+ "anArray contains consecutive, ordered squares that are all either in rank 8 or in rank 1"
+
+ | ppos |
+
+ ppos := Array streamContents: [:str |
+ str nextPut: anArray first - 1.
+ "If the king does not move, castling is not prevented by a pawn in same file"
+ anArray size > 1 ifTrue: [str nextPutAll: anArray].
+ str nextPut: anArray last + 1].
+
+ ^ self checkUnprotectedAttack:
+ (ppos + (myPlayer isWhitePlayer ifTrue: [8] ifFalse: [-8]))
+ fromPiece: Pawn!

Item was added:
+ ----- Method: Chess960MoveGenerator>>checkRookMoversAttacksAlong: (in category 'support') -----
+ checkRookMoversAttacksAlong: anArray
+
+ "anArray contains consecutive, ordered squares that are all either in rank 8 or in rank 1"
+
+ anArray first > 8 ifTrue: [ "black"
+ anArray do: [:s |
+ (self checkAttack: {s-8. s-16. s-24. s-32. s-40. s-48. s-56} fromPieces: RookMovers)
+ ifTrue: [^ true]].
+ ^ false].
+
+ "white"
+ anArray do: [:s |
+ (self checkAttack: {s+8. s+16. s+24. s+32. s+40. s+48. s+56} fromPieces: RookMovers)
+ ifTrue: [^ true]].
+ ^ false
+ !

Item was added:
+ ----- Method: Chess960MoveGenerator>>moveBlackKingAt: (in category 'moves-general') -----
+ moveBlackKingAt: square
+ | capture |
+ (KingMoves at: square) do:[:destSquare|
+ (myPieces at: destSquare) = 0 ifTrue:[
+ capture := itsPieces at: destSquare.
+ (forceCaptures and:[capture = 0]) ifFalse:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ move: King from: square to: destSquare capture: capture.
+ capture = King ifTrue:[kingAttack := moveList at: lastMoveIndex].
+ ].
+ ].
+ ].
+ forceCaptures ifTrue:[^self].
+ "now consider castling"
+ self canCastleBlackKingSide ifTrue:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ moveCastlingKingSide: King from: square to: G8
+ ].
+ self canCastleBlackQueenSide ifTrue:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ moveCastlingQueenSide: King from: square to: C8
+ ].!

Item was added:
+ ----- Method: Chess960MoveGenerator>>moveWhiteKingAt: (in category 'moves-general') -----
+ moveWhiteKingAt: square
+ | capture |
+ (KingMoves at: square) do:[:destSquare|
+ (myPieces at: destSquare) = 0 ifTrue:[
+ capture := itsPieces at: destSquare.
+ (forceCaptures and:[capture = 0]) ifFalse:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ move: King from: square to: destSquare capture: capture.
+ capture = King ifTrue:[kingAttack := moveList at: lastMoveIndex].
+ ].
+ ].
+ ].
+ forceCaptures ifTrue:[^self].
+ "now consider castling"
+ self canCastleWhiteKingSide ifTrue:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ moveCastlingKingSide: King from: square to: G1.
+ ].
+ self canCastleWhiteQueenSide ifTrue:[
+ (moveList at: (lastMoveIndex := lastMoveIndex + 1))
+ moveCastlingQueenSide: King from: square to: C1.
+ ].!

Item was added:
+ ChessPlayer subclass: #Chess960Player
+ instanceVariableNames: 'configuration'
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !Chess960Player commentStamp: 'spfa 6/2/2020 15:16' prior: 0!
+ Chess960Player represents a Chess960 player (doh)!

Item was added:
+ ----- Method: Chess960Player>>addBlackPieces: (in category 'adding/removing') -----
+ addBlackPieces: aChess960Configuration
+
+ self configuration: aChess960Configuration.
+
+ configuration positions doWithIndex: [:p :n | self addPiece: p at: 56+n].
+ 49 to: 56 do:[:i| self addPiece: Pawn at: i].!

Item was added:
+ ----- Method: Chess960Player>>addWhitePieces: (in category 'adding/removing') -----
+ addWhitePieces: aChess960Configuration
+
+ self configuration: aChess960Configuration.
+
+ configuration positions doWithIndex: [:p :n | self addPiece: p at: n].
+ 9 to: 16 do:[:i| self addPiece: Pawn at: i].
+ !

Item was added:
+ ----- Method: Chess960Player>>applyCastleKingSideMove: (in category 'moving') -----
+ applyCastleKingSideMove: move
+
+ (pieces at: move destinationSquare) isZero "rook" ifFalse: [
+ castlingRookSquare := self isWhitePlayer ifTrue: [F1] ifFalse: [F8].
+ move sourceSquare = castlingRookSquare
+ ifTrue: [
+ self swapPiecesIn: move sourceSquare and: move destinationSquare]
+ ifFalse: [
+ self movePiece: Rook from: self initialRightRookSquare to: castlingRookSquare.
+ self movePiece: King from: move sourceSquare to: move destinationSquare].
+ castlingStatus := castlingStatus bitOr: CastlingDone.
+ ^ self].
+
+ self movePiece: move movingPiece from: move sourceSquare to: move destinationSquare.
+ self movePiece: Rook
+ from: self initialRightRookSquare
+ to: ((castlingRookSquare := self isWhitePlayer ifTrue: [F1] ifFalse: [F8])).
+ pieces at: castlingRookSquare put: King.
+ castlingStatus := castlingStatus bitOr: CastlingDone.!

Item was added:
+ ----- Method: Chess960Player>>applyCastleQueenSideMove: (in category 'moving') -----
+ applyCastleQueenSideMove: move
+
+ (pieces at: move destinationSquare) isZero "rook or king" ifFalse: [
+ castlingRookSquare := self isWhitePlayer ifTrue: [D1] ifFalse: [D8].
+ move sourceSquare = castlingRookSquare
+ ifTrue: [
+ self swapPiecesIn: move sourceSquare and: move destinationSquare]
+ ifFalse: [
+ self movePiece: Rook
+ from: self initialLeftRookSquare to: castlingRookSquare.
+ self movePiece: King from: move sourceSquare to: move destinationSquare].
+ castlingStatus := castlingStatus bitOr: CastlingDone.
+ ^ self].
+
+ self movePiece: move movingPiece from: move sourceSquare to: move destinationSquare.
+ self movePiece: Rook
+ from: self initialLeftRookSquare
+ to: (castlingRookSquare := self isWhitePlayer ifTrue: [D1] ifFalse: [D8]).
+ pieces at: castlingRookSquare put: King.
+ castlingStatus := castlingStatus bitOr: CastlingDone.!

Item was added:
+ ----- Method: Chess960Player>>configuration (in category 'configuration') -----
+ configuration
+
+ ^ configuration!

Item was added:
+ ----- Method: Chess960Player>>configuration: (in category 'configuration') -----
+ configuration: aChess960Configuration
+
+ configuration := aChess960Configuration!

Item was added:
+ ----- Method: Chess960Player>>copyPlayer: (in category 'copying') -----
+ copyPlayer: aPlayer
+
+ super copyPlayer: aPlayer.
+ configuration := aPlayer configuration!

Item was added:
+ ----- Method: Chess960Player>>initialKingSquare (in category 'configuration') -----
+ initialKingSquare
+
+ ^ self isWhitePlayer ifTrue: [self configuration initialKingPosition]
+ ifFalse: [self configuration initialKingPosition + 56]!

Item was added:
+ ----- Method: Chess960Player>>initialLeftRookSquare (in category 'configuration') -----
+ initialLeftRookSquare
+
+ ^ self isWhitePlayer ifTrue: [self configuration initialLeftRookPosition]
+ ifFalse: [self configuration initialLeftRookPosition + 56]!

Item was added:
+ ----- Method: Chess960Player>>initialRightRookSquare (in category 'configuration') -----
+ initialRightRookSquare
+
+ ^ self isWhitePlayer ifTrue: [self configuration initialRightRookPosition]
+ ifFalse: [self configuration initialRightRookPosition + 56]!

Item was added:
+ ----- Method: Chess960Player>>leftCastlingField (in category 'configuration') -----
+ leftCastlingField
+
+ "The squares walked by both the king and the left rook when castling to the left - they must  be clear of other pieces"
+
+ ^ self isWhitePlayer
+ ifTrue: [(C1 to: self initialKingSquare) union: (self initialLeftRookSquare to: D1)]
+ ifFalse: [(C8 to: self initialKingSquare) union: (self initialLeftRookSquare to: D8)]
+ !

Item was added:
+ ----- Method: Chess960Player>>leftCastlingWalk (in category 'configuration') -----
+ leftCastlingWalk
+
+ "The squares walked by the king when castling to the left - they must not be under check"
+
+ | ks |
+
+ ks := self initialKingSquare.
+
+ ^ self isWhitePlayer
+ ifTrue: [ks > C1 ifTrue: [C1 to: ks] ifFalse: [ks to: C1]]
+ ifFalse: [ks > C8 ifTrue: [C8 to: ks] ifFalse: [ks to: C8]] !

Item was added:
+ ----- Method: Chess960Player>>movePiece:from:to: (in category 'adding/removing') -----
+ movePiece: piece from: sourceSquare to: destSquare
+
+ sourceSquare = destSquare ifTrue: [^ self].
+ super movePiece: piece from: sourceSquare to: destSquare!

Item was added:
+ ----- Method: Chess960Player>>rightCastlingField (in category 'configuration') -----
+ rightCastlingField
+
+ "The squares walked by both the king and the right rook when castling to the left - they must  be clear of other pieces"
+
+ ^ self isWhitePlayer
+ ifTrue: [(self initialKingSquare to: G1) union: (F1 to: self initialRightRookSquare)]
+ ifFalse: [(self initialKingSquare to: G8) union: (F8 to: self initialRightRookSquare)]!

Item was added:
+ ----- Method: Chess960Player>>rightCastlingWalk (in category 'configuration') -----
+ rightCastlingWalk
+
+ "The squares walked by the king when castling to the right - they must not be under check"
+
+ | ks |
+
+ ks := self initialKingSquare.
+
+ ^ self isWhitePlayer
+ ifTrue: [ks > G1 ifTrue: [G1 to: ks] ifFalse: [ks to: G1]]
+ ifFalse: [ks > G8 ifTrue: [G8 to: ks] ifFalse: [ks to: G8]] !

Item was added:
+ ----- Method: Chess960Player>>swapPiecesIn:and: (in category 'adding/removing') -----
+ swapPiecesIn: aSquare and: bSquare
+
+ "Only applies to specific castling moves"
+
+ | score pa pb |
+
+ pa := pieces at: aSquare.
+ pb := pieces at: bSquare.
+
+ score := PieceCenterScores at: pa.
+ positionalValue := positionalValue - (score at: aSquare).
+ positionalValue := positionalValue + (score at: bSquare).
+
+ score := PieceCenterScores at: pb.
+ positionalValue := positionalValue - (score at: bSquare).
+ positionalValue := positionalValue + (score at: aSquare).
+
+ pieces at: aSquare put: pb.
+ pieces at: bSquare put: pa.
+ board updateHash: pa at: aSquare from: self.
+ board updateHash: pa at: bSquare from: self.
+ board updateHash: pb at: bSquare from: self.
+ board updateHash: pb at: aSquare from: self.
+
+ self userAgent ifNotNil:[self userAgent swappedPieceOn: aSquare withPieceOn: bSquare].!

Item was added:
+ ----- Method: Chess960Player>>undoCastleKingSideMove: (in category 'undo') -----
+ undoCastleKingSideMove: move
+ self prepareNextMove. "in other words, remove extra kings"
+ self movePiece: move movingPiece from: move destinationSquare to: move sourceSquare.
+
+ self isWhitePlayer ifTrue: [
+ self movePiece: Rook from: F1 to: self initialRightRookPosition.
+ ] ifFalse: [
+ self movePiece: Rook from: F8 to: self initialRightRookPosition + 56.
+ ]
+
+ !

Item was added:
+ ----- Method: Chess960Player>>undoCastleQueenSideMove: (in category 'undo') -----
+ undoCastleQueenSideMove: move
+ self prepareNextMove. "in other words, remove extra kings"
+ self movePiece: move movingPiece from: move destinationSquare to: move sourceSquare.
+
+ self isWhitePlayer ifTrue: [
+ self movePiece: Rook from: D1 to: self initialLeftRookPosition.
+ ] ifFalse: [
+ self movePiece: Rook from: D8 to: self initialLeftRookPosition + 56.
+ ]
+
+ !

Item was added:
+ ----- Method: Chess960Player>>updateCastlingStatus: (in category 'moving') -----
+ updateCastlingStatus: move
+
+ "Cannot castle when king has moved"
+ (move movingPiece = King)
+ ifTrue:[^castlingStatus := castlingStatus bitOr: CastlingDisableAll].
+
+ "See if a rook has moved"
+ (move movingPiece = Rook) ifFalse:[^self].
+
+ (move sourceSquare = self initialLeftRookSquare)
+ ifTrue:[^castlingStatus := castlingStatus bitOr: CastlingDisableQueenSide].
+
+ (move sourceSquare = self initialRightRookSquare)
+ ifTrue:[^castlingStatus := castlingStatus bitOr: CastlingDisableKingSide].!

Item was changed:
  ----- Method: ChessBoard>>movePieceFrom:to: (in category 'moving') -----
  movePieceFrom: sourceSquare to: destSquare
  | move |
  searchAgent isThinking ifTrue:[^self].
  move := (activePlayer findPossibleMovesAt: sourceSquare) contents
+ detect:[:any| any destinationSquare = destSquare
+ or: [(any triggerSquareIn: self) = destSquare]].
- detect:[:any| any destinationSquare = destSquare].
  self nextMove: move.
  searchAgent activePlayer: activePlayer.!

Item was changed:
  ----- Method: ChessMorph>>showMovesAt: (in category 'events') -----
  showMovesAt: square
  | list |
  board ifNil:[^self].
  board searchAgent isThinking ifTrue:[^self].
  self squaresDo:[:m| m borderWidth: 0].
  list := board activePlayer findValidMovesAt: square.
  list isEmpty ifTrue:[^self].
  (self atSquare: square) borderWidth: 1.
  list do:[:move|
+ (self atSquare: (move triggerSquareIn: board)) borderWidth: 1.
- (self atSquare: move destinationSquare) borderWidth: 1.
  ].!

Item was added:
+ ----- Method: ChessMove>>triggerSquareIn: (in category 'accessing') -----
+ triggerSquareIn: aChessBoard
+
+ type = MoveCastlingKingSide ifTrue: [^ aChessBoard activePlayer initialRightRookSquare].
+ type = MoveCastlingQueenSide ifTrue: [^ aChessBoard activePlayer initialLeftRookSquare].
+
+ ^destinationSquare!

Item was changed:
  ----- Method: ChessMoveGenerator>>canCastleBlackKingSide (in category 'support') -----
  canCastleBlackKingSide
  (castlingStatus bitAnd: CastlingEnableKingSide) = 0 ifFalse:[^false].
  "Quickly check if all the squares are zero"
  ((myPieces at: G8) + (myPieces at: F8) + (itsPieces at: G8) + (itsPieces at: F8) = 0) ifFalse:[^false].
  "Check for castling squares under attack..  See canCastleBlackQueenSide for details"
- (self checkAttack:{H7. H6. H5. H4. H3. H2. H1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{G7. G6. G5. G4. G3. G2. G1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{F7. F6. F5. F4. F3. F2. F1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{E7. E6. E5. E4. E3. E2. E1.} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{D8. C8. B8. A8} fromPieces:RookMovers) ifTrue:[^false].
- (self checkAttack:{G7. F6. E5. D4. C3. B2. A1} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F7. E6. D5. C4. B3. A2} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{E7. D6. C5. B4. A3} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D7. C6. B5. A4} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F7. G6. H5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{G7. H6} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{H7} fromPieces:BishopMovers) ifTrue:[^false].
+ (self checkUnprotectedAttack:{H7. G7. E7. D7. C7. H6. G6. F6. E6. D6} fromPiece:Knight) ifTrue:[^false].
- (self checkUnprotectedAttack:{H7. G7. F7. E7. D7. C7. H6. G6. F6. E6. D6} fromPiece:Knight) ifTrue:[^false].
  (self checkUnprotectedAttack:{H7. G7. F7. E7. D7} fromPiece:Pawn) ifTrue:[^false].
+ (self checkUnprotectedAttack:{G7} fromPiece:King) ifTrue:[^false].
+
  ^true.
 
 
 
 
  !

Item was changed:
  ----- Method: ChessMoveGenerator>>canCastleBlackQueenSide (in category 'support') -----
  canCastleBlackQueenSide
  (castlingStatus bitAnd: CastlingEnableQueenSide) = 0 ifFalse:[^false].
  "Quickly check if all the squares are zero"
  ((myPieces at: B8) +  (myPieces at: C8) +  (myPieces at: D8) +
  (itsPieces at: B8) + (itsPieces at: C8) + (itsPieces at: D8)
  = 0) ifFalse:[^false].
  "Check to see if any of the squares involved in castling are under attack.  First
  check for vertical (rook-like) attacks"
- (self checkAttack:{A7. A6. A5. A4. A3. A2. A1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{B7. B6. B5. B4. B3. B2. B1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{C7. C6. C5. C4. C3. C2. C1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{D7. D6. D5. D4. D3. D2. D1} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{E7. E6. E5. E4. E3. E2. E1} fromPieces:RookMovers) ifTrue:[^false].
  "Check for a rook attack from the baseline"
  (self checkAttack:{F8. G8. H8} fromPieces:RookMovers) ifTrue:[^false].
  "Check for bishop attacks from the diagonals"
- (self checkAttack:{B7. C6. D5. E4. F3. G2. H1} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{C7. D6. E5. F4. G3. H2} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D7. E6. F5. G4. H3} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{E7. F6. G5. H4} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F7. G6. H5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{A7} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{B7. A6} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{C7. B6. A5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D7. C6. B5. A4} fromPieces:BishopMovers) ifTrue:[^false].
  "Check for a knight attack"
  (self checkUnprotectedAttack:{A7. B7. C7. D7. E7. F7. G7. A6. B6. C6. D6. E6. F6} fromPiece:Knight) ifTrue:[^false].
  "check for a pawn attack"
  (self checkUnprotectedAttack:{A7. B7. C7. D7. E7. F7} fromPiece:Pawn) ifTrue:[^false].
  "check for a king attack"
  (self checkUnprotectedAttack:{B7. C7. } fromPiece:King) ifTrue:[^false].
  ^true.
  !

Item was changed:
  ----- Method: ChessMoveGenerator>>canCastleWhiteKingSide (in category 'support') -----
  canCastleWhiteKingSide
  (castlingStatus bitAnd: CastlingEnableKingSide) = 0 ifFalse: [^false].
  "Quickly check if all the squares are zero"
  ((myPieces at:G1) + (myPieces at:F1) + (itsPieces at:G1) + (itsPieces at:F1) = 0) ifFalse:[^false].
  "Check for castling squares under attack..  See canCastleBlackQueenSide for details"
- (self checkAttack:{H2. H3. H4. H5. H6. H7. H8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{G2. G3. G4. G5. G6. G7. G8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{F2. F3. F4. F5. F6. F7. F8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{E2. E3. E4. E5. E6. E7. E8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{A1. A2. A3. A4} fromPieces:RookMovers) ifTrue:[^false].
- (self checkAttack:{G2. F3. E4. D5. C6. B7. A8} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F2. E3. D4. C5. B6. A7} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{E2. D3. C4. B5. A6} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D2. C3. B4. A5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F2. G3. H4} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{G2. H3} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{H2} fromPieces:BishopMovers) ifTrue:[^false].
+ (self checkUnprotectedAttack:{H2. G2. E2. D2. C2. H3. G3. F3. E3. D3} fromPiece:Knight) ifTrue:[^false].
- (self checkUnprotectedAttack:{H2. G2. F2. E2. D2. C2. H3. G3. F3. E3. D3} fromPiece:Knight) ifTrue:[^false].
  (self checkUnprotectedAttack:{H2. G2. F2. E2. D2} fromPiece:Pawn) ifTrue:[^false].
  (self checkUnprotectedAttack:{G2} fromPiece:King) ifTrue:[^false].
  ^true.!

Item was changed:
  ----- Method: ChessMoveGenerator>>canCastleWhiteQueenSide (in category 'support') -----
  canCastleWhiteQueenSide
  (castlingStatus bitAnd: CastlingEnableQueenSide) = 0 ifFalse: [^false].
  "Quickly check if all the squares are zero"
  ((myPieces at:B1) + (myPieces at:C1) + (myPieces at:D1) +
  (itsPieces at:B1) + (itsPieces at:C1) + (itsPieces at:D1) = 0) ifFalse:[^false].
  "Check for castling squares under attack..  See canCastleBlackQueenSide for details"
- (self checkAttack:{A2. A3. A4. A5. A6. A7. A8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{B2. B3. B4. B5. B6. B7. B8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{C2. C3. C4. C5. C6. C7. C8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{D2. D3. D4. D5. D6. D7. D8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{E2. E3. E4. E5. E6. E7. E8} fromPieces:RookMovers) ifTrue:[^false].
  (self checkAttack:{F1. G1. H1} fromPieces:RookMovers) ifTrue:[^false].
- (self checkAttack:{B2. C3. D4. E5. F6. G7. H8} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{C2. D3. E4. F5. G6. H7} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D2. E3. F4. G5. H6} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{E2. F3. G4. H5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{F2. G3. H4} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{A2} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{B2. A3} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{C2. B3. A4} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkAttack:{D2. C3. B4. A5} fromPieces:BishopMovers) ifTrue:[^false].
  (self checkUnprotectedAttack:{A2. B2. C2. D2. E2. F2. G2. A3. B3. C3. D3. E3. F3} fromPiece:Knight) ifTrue:[^false].
  (self checkUnprotectedAttack:{A2. B2. C2. D2. E2. F2} fromPiece:Pawn) ifTrue:[^false].
  (self checkUnprotectedAttack:{B2. C2} fromPiece:King) ifTrue:[^false].
  ^true.!

Item was added:
+ ChessPieceMorph subclass: #ChessPieceMorphWC
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'Etoys-Squeakland-Morphic-Games-Chess960'!
+
+ !ChessPieceMorphWC commentStamp: 'spfa 5/31/2020 10:36' prior: 0!
+ ChessPieceMorphWC class side provides scalable images from Wikimedia Commons!

Item was added:
+ ----- Method: ChessPieceMorphWC class>>pieceExtent (in category 'forms library') -----
+ pieceExtent
+
+ ^ 314 @ 302!

Item was added:
+ ----- Method: ChessPieceMorphWC class>>pieces (in category 'forms library') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: ChessPieceMorphWC class>>piecesWithExtent: (in category 'forms library') -----
+ piecesWithExtent: aPoint
+
+ | form dict ng og pg i ib iw |
+
+ form := self pieces.
+ dict := Dictionary new.
+ ng := #( whiteKing  blackKing whiteQueen blackQueen whiteBishop blackBishop whiteKnight  blackKnight whiteRook blackRook whitePawn blackPawn).
+
+ og := #(55 55 10 10 0 0 0 0 0 0 0 0).
+ pg := #(0 0 0 0 20 20 50 50 90 90 120 120).
+
+ i := 0.
+ 0 to: 5 do: [:n |
+ ib := (i := i + 1) * 2 - 1.
+ iw := i * 2.
+ dict at: (ng at: ib)
+ put: ((form contentsOfArea: (315 * n + (pg at: ib) @0
+ corner: 315 * n + 314 - (og at: ib) @ 302))
+ scaledToSize: aPoint).
+ dict at: (ng at: iw)
+ put: ((form contentsOfArea: (315 * n + (pg at: iw) @327
+ corner: 315 * n + 314 - (og at: iw) @ 629))
+ scaledToSize: aPoint)].
+
+ ^ dict!

Item was added:
+ ----- Method: ChessPieceMorphWC class>>piecesWithHeight: (in category 'forms library') -----
+ piecesWithHeight: anInteger
+
+ ^ self piecesWithExtent: self pieceExtent x * anInteger / self pieceExtent y @ anInteger!

Item was changed:
  ----- Method: ChessPlayer>>applyEnpassantMove: (in category 'moving') -----
  applyEnpassantMove: move
+ | capturedSquare |
+ capturedSquare := move destinationSquare - (self isWhitePlayer ifTrue:[8] ifFalse:[-8]).
+ opponent removePiece: move capturedPiece at: capturedSquare.
+ self userAgent ifNotNil:[(self userAgent atSquare: capturedSquare) removeAllMorphs].
- opponent removePiece: move capturedPiece at: move destinationSquare -
- (self isWhitePlayer ifTrue:[8] ifFalse:[-8]).
  ^self movePiece: move movingPiece from: move sourceSquare to: move destinationSquare!

Item was changed:
  ----- Method: ChessPlayer>>evaluateMaterial (in category 'evaluation') -----
  evaluateMaterial
  "Compute the board's material balance, from the point of view of the side
  player.  This is an exact clone of the eval function in CHESS 4.5"
+ | total diff value pawns |
- | total diff value |
  self materialValue = opponent materialValue ifTrue:[^0]. "both sides are equal"
  total := self materialValue + opponent materialValue.
  diff := self materialValue - opponent materialValue.
+
+ pawns := numPawns.
+ pawns < 0 ifTrue: ["happens - a bug somewhere" pawns := 0].
+
  value := (2400 min: diff) +
+ ((diff * (12000 - total) * pawns) // (6400 * (pawns + 1))).
- ((diff * (12000 - total) * self numPawns) // (6400 * (self numPawns + 1))).
  ^value!

Item was added:
+ ----- Method: ChessPlayer>>initialLeftRookSquare (in category 'configuration') -----
+ initialLeftRookSquare
+
+ ^ self isWhitePlayer ifTrue: [A1] ifFalse: [A8]!

Item was added:
+ ----- Method: ChessPlayer>>initialRightRookSquare (in category 'configuration') -----
+ initialRightRookSquare
+
+ ^ self isWhitePlayer ifTrue: [H1] ifFalse: [H8]!

Item was changed:
  ----- Method: ChessPlayer>>isValidMoveFrom:to: (in category 'testing') -----
  isValidMoveFrom: sourceSquare to: destSquare
  | move |
  move := (self findValidMovesAt: sourceSquare)
+ detect:[:any| (any triggerSquareIn: board) = destSquare] ifNone:[nil].
- detect:[:any| any destinationSquare = destSquare] ifNone:[nil].
  ^move notNil!

Item was changed:
  ----- Method: ChessPlayer>>removePiece:at: (in category 'adding/removing') -----
  removePiece: piece at: square
+
+ (pieces at: square) = piece ifFalse: ["fix"
+ "Happens at time - some moves have a capturedPiece absent from the board"
+ ^self].
+
  pieces at: square put: 0.
  materialValue := materialValue - (PieceValues at: piece).
  positionalValue := positionalValue - ((PieceCenterScores at: piece) at: square).
  piece = Pawn ifTrue:[numPawns := numPawns - 1].
  board updateHash: piece at: square from: self.
+ self userAgent ifNotNil:[self userAgent removedPiece: piece at: square].
+ !
- self userAgent ifNotNil:[self userAgent removedPiece: piece at: square].!

Item was changed:
  ----- Method: ChessPlayerAI>>statusString (in category 'accessing') -----
  statusString
  | av count |
  ^String streamContents:[:s|
  (myMove == #none or:[myMove == nil]) ifFalse:[
+ s print: myMove value / 100.0; space.
- s print: myMove value * 0.01; space.
  ].
  av := bestVariation.
  count := av at: 1.
  count > 0 ifFalse:[
  av := activeVariation.
  count := av at: 1].
  count > 0 ifFalse:[
  s nextPutAll:'***'.
  av := variations at: 1.
  count := av at: 1.
  count > 3 ifTrue:[count := 3]].
  2 to: count + 1 do:[:index|
  s nextPutAll: (ChessMove decodeFrom: (av at: index)) moveString.
  s space].
 
  s nextPut:$[.
  s print: nodesVisited.
  " s nextPut:$|.
  s print: ttHits.
  s nextPut: $|.
  s print: alphaBetaCuts.
  " s nextPut:$].
 
  ].!