Chess

Blitz3D Forums/Blitz3D Programming/Chess

Rook Zimbabwe(Posted 2004) [#1]
Anyone have an idea where I could find the basic code for a chess logic engine?


Rook Zimbabwe(Posted 2004) [#2]
OK so I admit I don't want to do the really hard part... but there has been code for this floating around for years... I don't want to do an Othello game... I want to see how a more difficult game is done.

-RZ


jhocking(Posted 2004) [#3]
Look up minimax chess algorithms on Google.


Picklesworth(Posted 2004) [#4]
A* pathfinding also seems fairly useful for a chess game AI. There's a tutorial for it at www.blitzcoder.com


Cancerian(Posted 2004) [#5]
I stumbled across a book at my local library the other day that could probably help you. It was called "How Computers Play Chess", do a search and you can probably find it.


Almo(Posted 2004) [#6]
A good Othello program isn't really that simple... I've worked on one for a long time, and it's now pretty good. Thing is, when you get into it, you find all the subtleties.

Interestingly enough, Chinook (Best Checkers program) was started by a guy trying to prove how silly a game Checkers was. He came to love it.

So if Chess overwhelms you (its rules exceptions cause problems), try Othello. You might like it. :D


_PJ_(Posted 2004) [#7]
Two ways of looking at it...

Chess is complicated AI (because you need to include all the pieces, their avcailable moves, tactics AND the rules)

or

Chess is simple AI because its just a comparison of numbers...

I put something about how I would code chess AI here somewhere....

here in fact!


Wayne(Posted 2004) [#8]
This would need converting to Blitz.
Hope it helps.
True Basic Source follows:

;Chess  -  updated 3/2/02 v.102
;This is a simple chess program written in True BASIC 
;
;Even the fastest BASIC compiler is incapable of creating an efficient chess
;program. It's the nature of the language. And I don't even try to accomplish that
;here. My goal was simply to create a program that could play sensible chess, and yet
;be comprehensible to someone looking at the code. I've seen too many spaghetti code
;programs, or programs barely able to make legal moves. This program hopefully balances
;coherent code with reasonable play. (For a truly ambitious BASIC chess program, go
;to http://digilander.iol.it/larsenvb/index_e.htm)
;
;Although it contains a graphical interface, this program is no-frills. It will not
;check your moves for legality. It will not let you take back your moves. It will
;not play by a clock. It cannot be forced to make a move before it's ready.
;But hopefully you'll have fun tinkering with it. The source code is free. Use
;however you wish.
;
;ergundel@...


PROGRAM CHESS(PositionCSV$)       ; load simple command line CSV file as starting position, if supplied

OPTION TYPO
RANDOMIZE

SET MODE "color256"               ; Windows video mode - does nothing in dos

LIBRARY "BTreeLib.trc"            ; compiled binary tree routines for searching book moves
LOCAL BookExists

WHEN error in                     ; If opening book file exits, use, else, ignore
     OPEN #1: name "opnbook.bt", create old, access input, org byte
     CLOSE #1                     ; cause error if file isn't there
     CALL BTOpen("opnbook.bt", BookExists, #2)
USE
     LET BookExists=0
END WHEN

LOCAL BestFromR(1 to 4), BestFromC(1 to 4), BestToR(1 to 4), BestToC(1 to 4),x,y
LOCAL MaxRow,MaxCol,MaxPlyLevel,MaxExtendedPlys, BoardPic$,BlackSquare$,WhiteSquare$,turn
LOCAL fromX,fromY,toX,toY,mouseoption,besteval,NumberEvaluated, MoveCount
LOCAL MoveList$,BookLine$,note$,found,randx,tmp$,CastleFlag,SelfPlay$,colstr$
LET colstr$="abcdefgh"

DECLARE FUNCTION Notate$

LET CastleFlag=1


PRINT "Press Any Key To Begin, or ""A"" to begin autoplay";
GET KEY x

IF x<255 and ucase$(chr$(x))="A" then
   LET SelfPlay$="Y"
   IF ucase$(trim$(SelfPlay$))[1:1]="Y" then LET SelfPlay$="Y"
END IF

; Write game to pgn file
OPEN #1: name "game.pgn", org text, create newold, access outin
ERASE #1

; set default level
LET MaxPlyLevel=2
LET MaxExtendedPlys=2             ;ideally, Extended Plys+MaxPlies should be an even number

SET WINDOW 0, 22, -6, 9.5
ASK MAX CURSOR MaxRow,MaxCol      ; find window limits

DIM board(1 to 8, 1 to 8)

; Load position from CSV file, else load normal starting position
IF PositionCSV$="" then
   ; first call merely sets up the board
   CALL MakeMove(board,0,0,0,0,0,BestFromR(),BestFromC(),BestToR(),BestToC(),MoveList$,0)
ELSE
   PRINT "Reading position from ";PositionCSV$   ; position in CSV, no frills
   OPEN #3: name PositionCSV$, org text, create old, access input
   MAT INPUT #3: board
   CLOSE #3
END IF

CALL drawboard(board,boardpic$,BlackSquare$,WhiteSquare$)

LET turn=-1
LET MoveCount=1

DO
   LET NumberEvaluated = 0
   SET CURSOR MaxRow-6,1
   SET BACK "black"
   SET COLOR "white"

;         ;; uncomment next block to auto-run two play levels against each other
;         IF turn=1 then                 ;starts with black (changed later before move)
;            LET MaxPlyLevel=2
;            LET MaxExtendedPlys=2
;         ELSE                           ;white
;            LET MaxPlyLevel=2
;            LET MaxExtendedPlys=0
;         END IF

   IF besteval>=70 then
      CALL resign
   ELSEIF besteval<=-99 then
      PRINT "**  you lose  **"
      STOP
   ELSE
   END IF

   IF SelfPlay$<>"Y" then
      PRINT "your turn (A-Autoplay, R-Refresh, Q-Quit, Level 1,2,3,4,5,6)";
      SOUND 1000,.01
      DO                          ; loop until move is made
         DO                       ; loop through user options
            GET MOUSE fromY,fromX,mouseoption
            IF key input then
               GET KEY x
               IF x<256 then
                  SELECT CASE chr$(x)
                  CASE "Q","q"
                       STOP
                  CASE "A","a"
                       LET SelfPlay$="Y"
                       PRINT "Auto-play will start after your next move"
                  CASE "R","r"
                       CLEAR
                       CALL drawboard(board,boardpic$,BlackSquare$,WhiteSquare$)
                       SET CURSOR MaxRow-6,1
                       SET COLOR "White"
                  CASE "1"
                       PRINT "Setting to play level 1"
                       LET MaxPlyLevel=2
                       LET MaxExtendedPlys=0
                  CASE "2"
                       PRINT "Setting to play level 2"
                       LET MaxPlyLevel=2
                       LET MaxExtendedPlys=2
                  CASE "3"
                       PRINT "Setting to play level 3"
                       LET MaxPlyLevel=3
                       LET MaxExtendedPlys=0
                  CASE "4"
                       PRINT "Setting to play level 4"
                       LET MaxPlyLevel=3
                       LET MaxExtendedPlys=1
                  CASE "5"
                       PRINT "Setting to play level 5 (analysis)"
                       LET MaxPlyLevel=4
                       LET MaxExtendedPlys=0
                  CASE "6"
                       PRINT "Setting to play level 6  (analysis)"
                       LET MaxPlyLevel=4
                       LET MaxExtendedPlys=2
                  CASE else
                  END SELECT
               END IF
            END IF
         LOOP until mouseoption = 1

         DO
            GET MOUSE toY,toX,mouseoption
         LOOP until mouseoption = 3
         LET fromX=int(fromX)
         LET fromY=int(fromY)
         LET toX=int(toX)
         LET toY=int(toY)

         IF  max(toX,max(toY,max(fromX,fromY)))<=8 and min(toX,min(toY,min(fromX,fromY)))>=1  and (fromX-toX<>0 or fromY-toY<>0) then
            WHEN error in
                 IF MoveCount=int(MoveCount) then
                    PRINT #1: trim$(str$(MoveCount)) & ". "& Notate$(fromX,fromY,toX,toY);" ";
                 ELSE
                    PRINT #1: Notate$(fromX,fromY,toX,toY)
                 END IF
                 LET MoveCount=MoveCount+0.5
            USE
            END WHEN
            EXIT DO
         END IF
      LOOP

      LET MoveList$=MoveList$ & Notate$(fromX,fromY,toX,toY)

      SET CURSOR MaxRow-6,1
      PRINT repeat$(" ",80)       ; blank line, clear out old text

      IF fromY<>toY and abs(board(fromX,fromY))=1 and board(toX,toY)=0 then    ; au passant
         LET board(fromX,toY)=0
         IF mod(toY+fromX,2)=1 then
            BOX SHOW WhiteSquare$ at fromX,toY
         ELSE
            BOX SHOW BlackSquare$ at fromX,toY
         END IF
      END IF

      LET board(toX,toY)=board(fromX,fromY)

      ; set castling flags, if moved piece is king or rook
      IF CastleFlag<210 and ((abs(board(fromX,fromY))=5 and (fromX*fromY=1 or fromX*fromY=8 or fromX*fromY=64)) or (abs(board(fromX,fromY))=99 and (fromX=1 or fromX=8) and fromY=5)) then CALL SetCastleFlag(fromX,fromY,CastleFlag)

      LET board(fromX,fromY)=0
      IF abs(board(toX,toY))=1 and (toX=1 or toX=8) then LET board(toX,toY)=9*board(toX,toY)  ; pawn to queen

      CALL MovePics(fromX,fromY,toX,toY,BlackSquare$,WhiteSquare$,board(toX,toY))

      ;  Castle
      IF abs(board(toX,toY)) = 99 and abs(fromY-toY)=2 then
         IF toY=7 then
            LET fromY=8
            LET toY=6
         ELSE
            LET fromY=1
            LET toY=4
         END IF
         LET board(toX,toY)=board(fromX,fromY)

         LET board(fromX,fromY)=0
         IF abs(board(toX,toY))=1 and (toX=1 or toX=8) then LET board(toX,toY)=9*board(toX,toY)    ; pawn to queen
         CALL MovePics(fromX,fromY,toX,toY,BlackSquare$,WhiteSquare$,board(toX,toY))
      END IF
   ELSE
      LET turn = -turn
   END IF

   IF BookExists<>0 then          ; get bookmoves
      CALL GetNearest(MoveList$, BookLine$, #2)
      LET note$="In Book"
      LET tmp$=BookLine$
      IF len(MoveList$)<=24 then LET randx=int(rnd*3000/(1+len(MoveList$))) else LET randx=int(rnd*5)
      FOR x=1 to randx
          CALL GetNext(BookLine$,#2)
          IF pos(BookLine$,MoveList$)=0 then
             LET BookLine$=tmp$
             EXIT FOR
          END IF
      NEXT x
   END IF
   IF BookExists=0 or pos(BookLine$,MoveList$)=0 or BookLine$=MoveList$ then
      LET note$=""
      LET BookExists=0            ; out of book
   ELSE
      LET BestFromC(MaxPlyLevel)=pos(colstr$,BookLine$[len(MoveList$)+1:len(MoveList$)+1])
      LET BestFromR(MaxPlyLevel)=val(BookLine$[len(MoveList$)+2:len(MoveList$)+2])
      LET BestToC(MaxPlyLevel)  =pos(colstr$,BookLine$[len(MoveList$)+3:len(MoveList$)+3])
      LET BestToR(MaxPlyLevel)  =val(BookLine$[len(MoveList$)+4:len(MoveList$)+4])
      LET MoveList$=MoveList$ & BookLine$[len(MoveList$)+1:len(MoveList$)+4]
   END IF
   IF BookExists=0 then
      CALL MakeMove(board(,),MaxPlyLevel,MaxExtendedPlys,turn,besteval,NumberEvaluated,BestFromR(),BestFromC(),BestToR(),BestToC(),MoveList$,CastleFlag)
      LET MoveList$=MoveList$ & Notate$(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel),BestToR(MaxPlyLevel),BestToC(MaxPlyLevel))
      SET CURSOR MaxRow-5,1
      PRINT "My Move: "&MoveList$[len(MoveList$)-3:maxnum]&"                        "
   END IF


   IF BestFromR(MaxPlyLevel)=0 then CALL resign

   IF abs(board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel)))=1 and (BestToR(MaxPlyLevel)=1 or BestToR(MaxPlyLevel)=8) then LET board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel))=9*board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel))  ; pawn to queen
   LET board(BestToR(MaxPlyLevel),BestToC(MaxPlyLevel))=board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel))
   CALL MovePics(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel),BestToR(MaxPlyLevel),BestToC(MaxPlyLevel),BlackSquare$,WhiteSquare$,board(BestToR(MaxPlyLevel),BestToC(MaxPlyLevel)))

   ; set castling flags, if moved piece is king or rook
   IF CastleFlag<210 and ((abs(board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel)))=5 and (BestFromR(MaxPlyLevel)*BestFromC(MaxPlyLevel)=1 or BestFromR(MaxPlyLevel)*BestFromC(MaxPlyLevel)=8 or BestFromR(MaxPlyLevel)*BestFromC(MaxPlyLevel)=64)) or (abs(board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel)))=99 and (BestFromR(MaxPlyLevel)=1 or BestFromR(MaxPlyLevel)=8) and BestFromC(MaxPlyLevel)=5)) then CALL SetCastleFlag(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel),CastleFlag)

   LET board(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel))=0

   ;  Castle
   IF abs(board(BestToR(MaxPlyLevel),BestToC(MaxPlyLevel))) = 99 and abs(BestFromC(MaxPlyLevel)-BestToC(MaxPlyLevel))=2 then
      IF BestToC(MaxPlyLevel)=7 then
         LET fromY=8
         LET toY=6
      ELSE
         LET fromY=1
         LET toY=4
      END IF
      LET board(BestFromR(MaxPlyLevel),toY)=board(BestFromR(MaxPlyLevel),fromY)
      LET board(BestFromR(MaxPlyLevel),fromY)=0
      CALL MovePics(BestFromR(MaxPlyLevel),fromY,BestFromR(MaxPlyLevel),toY,BlackSquare$,WhiteSquare$,board(BestFromR(MaxPlyLevel),toY))
   END IF


   IF key input then LET SelfPlay$=""  ; stop auto-play if key is pressed
   WHEN error in
        IF MoveCount=int(MoveCount) then
           PRINT #1: trim$(str$(MoveCount)) & ". "& Notate$(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel),BestToR(MaxPlyLevel),BestToC(MaxPlyLevel));" ";
        ELSE
           PRINT #1: Notate$(BestFromR(MaxPlyLevel),BestFromC(MaxPlyLevel),BestToR(MaxPlyLevel),BestToC(MaxPlyLevel))
        END IF
   USE
   END WHEN

   LET MoveCount=MoveCount+.5
LOOP


END

;___________________________________________________________________________________________________

; Main routine, accepting as input values board, MaxPlyLevel,MaxExtendedPlys,turn,MoveList$,CastleFlag
; BestFromR(),BestFromC(),BestToR(),BestToC(),besteval,NumberEvaluated (positions)
SUB MakeMove(board(,),MaxPlyLevel,MaxExtendedPlys,turn,besteval,NumberEvaluated,BestFromR(),BestFromC(),BestToR(),BestToC(),MoveList$,CastleFlag)
    LOCAL PlyLevel, z, y, a$
    LOCAL CurrentFromR(1 to 4), CurrentFromC(1 to 4), CurrentToR(1 to 4), CurrentToC(1 to 4), no_more_moves
    LOCAL CurrentEval, EvenOddSwitch

    LET EvenOddSwitch=sgn(mod(MaxPlyLevel,2)-0.5)

    RESTORE
    DIM directions(1 to 32)       ; Array of directions from which a square may be attacked (in row/column pairs)
    DATA -1,-2,  1,-2, -1,2,  1,2      ; knight moves
    DATA -2,-1,  2,-1, -2,1,  2,1
    DATA  0, 1,  1, 1,  1,0,  1,-1     ; eight directions
    DATA  0,-1, -1,-1, -1,0, -1,1
    MAT READ directions


    LET no_more_moves = -100      ; constant

    LET besteval=-turn*maxnum

    IF turn=0 then
       CALL setupboard(board)
    ELSE
       LET PlyLevel=MaxPlyLevel

       CALL scanmoves(PlyLevel+1,board(,),0,0,0,0,turn,BestFromR(),BestFromC(),BestToR(),BestToC(),besteval,CastleFlag)

    END IF

    ;___________________________________________________________________________________________________

    SUB scanmoves(PlyLevel_,board_(,),SubFromR_,SubFromC_,SubToR_,SubToC_, turn_,BestFromR_(),BestFromC_(),BestToR_(),BestToC_(), BestEval_,CastleFlag_)
        DECLARE FUNCTION PosEval,AskCastleFlag,attacked
        IF abs(besteval_)>9999 then LET besteval_=(turn_)*maxnum
        LOCAL PlyLevel,board(8,8), new_r, new_c, num, SubFromR, SubFromC,  rcount,ccount, x,y, BestEval
        LOCAL BestFromR(4),BestFromC(4),BestToR(4),BestToC(4),CastleFlag,LostKingFlag,TotalNumberPositions
        LOCAL king_r,king_c

        FOR y=1 to 8              ; make a copy of the board as if passed by value
            FOR x=1 to 8
                IF board_(x,y)<>0 then
                   IF board_(x,y)=turn*99 then
                      LET king_r=x
                      LET king_c=y
                   END IF
                END IF
                LET board(x,y) = board_(x,y)

            NEXT x
        NEXT y




        LET CastleFlag=CastleFlag_

        ; make move if square is empty, or opposite colored (exception - pawn can't take by pushing forward 
        IF PlyLevel_<=MaxPlyLevel and (board(SubToR_,SubToC_)=0 Or (Sgn(board(SubToR_,SubToC_))<>Sgn(board(SubFromR_,SubFromC_)) And (Abs(board(SubFromR_,SubFromC_))<>1 Or SubFromC_<>SubToC_))) then

           LET board(SubToR_,SubToC_)=board(SubFromR_,SubFromC_)

           ;pawn to queen
           IF abs(board(SubToR_,SubToC_))=1 and (SubToR_=1 or SubToR_=8) then LET board(SubToR_,SubToC_)=9*board(SubToR_,SubToC_)

           ; set castling flags, if moved piece is king or rook
           IF CastleFlag<210 and ((abs(board(SubFromR_,SubFromC_))=5 and (SubFromR_*SubFromC_=1 or SubFromR_*SubFromC_=8 or SubFromR_*SubFromC_=64)) or (abs(board(SubFromR_,SubFromC_))=99 and (SubFromR_=1 or SubFromR_=8) and SubFromC_=5)) then CALL SetCastleFlag(SubFromR_,SubFromC_,CastleFlag)

           LET board(SubFromR_,SubFromC_)=0

           LET CurrentFromR(PlyLevel_)= SubFromR_
           LET CurrentFromC(PlyLevel_)= SubFromC_
           LET CurrentToR(PlyLevel_)  = SubToR_
           LET CurrentToC(PlyLevel_)  = SubToC_
           IF abs(board(SubToR_,SubToC_)) = 99 and abs(SubFromC_-SubToC_)=2 then    ; Castle
              IF SubToC_=7 then
                 LET board(SubToR_,6)=board(SubFromR_,8)
                 LET board(SubFromR_,8)=0
              ELSE
                 LET board(SubToR_,4)=board(SubFromR_,1)
                 LET board(SubFromR_,1)=0
              END IF
           END IF
           IF  SubFromR_=king_r and SubFromC_=king_c then
              LET king_r=SubToR_
              LET king_c=SubToC_
           END IF

           ; checked, but not checked-king's turn (or king missing)
           IF king_r=0 or (-turn_=sgn(board(king_r,king_c)) and attacked(board(,),king_r,king_c,turn)=1) then
              EXIT SUB
           END IF
        ELSEIF PlyLevel_<=MaxPlyLevel then  ; illegal move, skip move-line
           EXIT SUB
        ELSE
        END IF


        IF PlyLevel_=1 Then       ; End of recursive search; eval current position

           ; if move is a capture (not pawn), add plys until no longer a capture
           IF MaxExtendedPlys<>0 and (((sgn(board_(CurrentToR(1),CurrentToC(1)))=-sgn(board_(CurrentFromR(1),CurrentFromC(1)))))) and (abs(board_(CurrentFromR(1),CurrentFromC(1)))<>1 or abs(board_(CurrentToR(1),CurrentToC(1)))<>1) then
              LOCAL BestFromRx(1),BestFromCx(1),BestToRx(1),BestToCx(1),boardx(0,0)
              MAT boardx = board
              CALL MakeMove(boardx(,),1,MaxExtendedPlys-1,1*turn_,CurrentEval,0,BestFromRx(),BestFromCx(),BestToRx(),BestToCx(),MoveList$,CastleFlag)

           ELSEIF MaxExtendedPlys=0 and (((sgn(board_(CurrentToR(1),CurrentToC(1)))=-sgn(board_(CurrentFromR(1),CurrentFromC(1)))))) and (abs(board_(CurrentFromR(1),CurrentFromC(1)))<>1 or abs(board_(CurrentToR(1),CurrentToC(1)))<>1) then
              LET CurrentEval=PosEval(board, turn_)

              ; if exchange at end of search, and taking piece is undefended, penalize
              IF attacked(board,CurrentToR(1),CurrentToC(1),sgn(board(CurrentToR(1),CurrentToC(1))))=1 and attacked(board,CurrentToR(1),CurrentToC(1),-sgn(board(CurrentToR(1),CurrentToC(1))))<>1 then
                 LET CurrentEval=CurrentEval - 0.72 * board(CurrentToR(1),CurrentToC(1))
              END IF
           ELSE
              LET CurrentEval=PosEval(board, turn_)
           END IF
           IF EvenOddSwitch*turn*CurrentEval>EvenOddSwitch*turn*BestEval_ then
              LET BestEval_=CurrentEval
              FOR x=1 to MaxPlyLevel
                  LET BestFromR_(x)= CurrentFromR(x)
                  LET BestFromC_(x)= CurrentFromC(x)
                  LET BestToR_(x)  = CurrentToR(x)
                  LET BestToC_(x)  = CurrentToC(x)
              NEXT x
           END IF
           EXIT SUB
        ELSEIF PlyLevel_=MaxPlyLevel and maxplylevel<>1 then
           CALL info(BestFromR_(),BestFromC_(),BestToR_(),BestToC_(),NumberEvaluated,besteval_,"",MaxPlyLevel)
        END IF


        LET besteval=(turn_)*maxnum    ; always start with the highest value for other side

        LET PlyLevel = PlyLevel_ -1


        FOR rcount=1 To 8
            FOR ccount=1 To 8
                IF board(rcount,ccount)<>0 Then  ; p
                   IF Sgn(board(rcount,ccount))=turn_ Then
                      LET num=1
                      DO          ; repeat thru all possible piece moves
                         SELECT CASE board(rcount,ccount)
                         CASE 1, -1    ; pawn
                              CALL pawnmove(rcount,ccount,num, board(,),1*turn_, new_r, new_c)     ; au passant Not yet implemented
                         CASE 3, -3    ; knight
                              CALL knightmove(rcount,ccount,num,new_r, new_c)
                         CASE 3.1, -3.1     ; bishop
                              CALL bishopmove(rcount,ccount,num,new_r, new_c,board(,))
                         CASE 5, -5    ; rook
                              CALL rookmove(rcount,ccount,num,new_r, new_c,board(,),CastleFlag)
                         CASE 9, -9    ; rook
                              CALL queenmove(rcount,ccount,num,new_r, new_c,board(,))
                         CASE 99, -99  ; king
                              CALL kingmove(rcount,ccount,num,new_r, new_c,board(,),CastleFlag)
                         END SELECT
                         IF new_r = no_more_moves then EXIT DO
                         IF new_r<>0 then

                            ; Recurse down
                            CALL scanmoves(PlyLevel,board(,),rcount,ccount,new_r, new_c, -1*turn_, BestFromR(),BestFromC(),BestToR(),BestToC(),BestEval,CastleFlag)

                            ;                            LET TotalNumberPositions=TotalNumberPositions+1
                         END IF
                         LET num=num+1
                      LOOP


                   END IF
                END IF
            NEXT ccount
        NEXT rcount


        IF BestFromR(1)=0 then    ; no move found
           IF attacked(board_(,),king_r,king_c,turn)=1 then
              LET besteval=-turn_*999-turn_*PlyLevel_      ; checkmate seen
           ELSE
              LET besteval=0      ; stalemate seen
           END IF
        END IF

        IF turn_*BestEval<turn_*BestEval_ then
           LET BestEval_  = BestEval   ;+ turn_*0.01*TotalNumberPositions
           FOR x=1 to maxplylevel
               LET BestFromR_(x) = BestFromR(x)
               LET BestFromC_(x) = BestFromC(x)
               LET BestToR_(x)   = BestToR(x)
               LET BestToC_(x)   = BestToC(x)

           NEXT x
        END IF

    END SUB

    ;___________________________________________________________________________________________________

    ; posEval evaluates the current position, with a positive evaluation favoring white
    ; and a negative eval favoring black. Currently, this routine incorporates very little
    ; chess knowledge. Improvements in chess knowledge could drastically improve play, and
    ; might well be worth a small cost in speed.

    FUNCTION posEval(board(,), turn)
        LOCAL eval, x, y, z, count, PieceCounter, KingOnEdge,wkx,wky,bkx,bky,UseMe

        FOR x=1 to 8              ; Simple Material Evaluation
            FOR y=1 to 8
                LET eval=eval+board(x,y)
                IF board(x,y)<>0 then LET PieceCounter=PieceCounter+1
            NEXT y
        NEXT x


        FOR x=1 to 8              ; evaluate pawn values
            FOR y=1 to 8
                IF board(x,y)<>0 then
                   IF board(x,y)=1 then
                      SELECT CASE x
                      CASE 4      ; fourth row
                           IF y=4 or y=5 then
                              LET eval=eval+.1
                           ELSEIF y=3 or y=6 then
                              LET eval=eval+.03
                           ELSE
                              ;no adjustment
                           END IF
                      CASE 5
                           LET eval=eval+.025
                      CASE 6
                           LET eval=eval+.2
                      CASE 7
                           LET eval=eval+.25

                           ; nothing blocking pawn, and nothing attacking queening square, give bonus
                           if board(8,y)=0 and attacked(board,8,y,1)=0 then let eval=eval+1

                      CASE 8
                           LET eval=eval+9
                           LET board(x,y)=9
                      CASE else
                           ; no bonus value
                      END SELECT

                      ; give bonus for pawn fork
                      IF y>1 and y<8 and board(x+1,y+1)<-1 and board(x+1,y-1)<-1 then
                         ; but only if pawn is defended (opposite of attacked)
                         IF attacked(board(,),x,y,-1)=1 then
                            LET eval=eval+board(x,y)  ; increase eval by one pawn's worth
                         END IF
                      END IF
                   ELSEIF board(x,y)=-1 then

                      SELECT CASE x
                      CASE 5      ; fourth row, black's perspective
                           IF y=4 or y=5 then
                              LET eval=eval-.1
                           ELSEIF y=3 or y=6 then
                              LET eval=eval-.03
                           ELSE
                              ; no adjustment
                           END IF

                      CASE 4
                           LET eval=eval-.025
                      CASE 3
                           LET eval=eval-.2
                      CASE 2
                           LET eval=eval-.25

                           ; nothing blocking pawn, and nothing attacking queening square, give bonus
                           if board(1,y)=0 and attacked(board,1,y,-1)=0 then let eval=eval-1

                      CASE 1
                           LET eval=eval-9
                           LET board(x,y)=-9
                      CASE else
                           ; no bonus value
                      END SELECT

                      ; give bonus for pawn fork
                      IF y>1 and y<8 and board(x-1,y+1)>1 and board(x-1,y-1)>1 then
                         ; but only if pawn is defended
                         IF attacked(board(,),x,y,1)=1 then
                            LET eval=eval-1      ; increase eval by one pawn's worth
                         END IF
                      END IF

                   ELSEIF abs(board(x,y))=3 then      ;knight
                      IF max(x,y)<7 and min(x,y)>2 then LET eval = eval + sgn(board(x,y)) * 0.3

                      ; check for knight fork
                      LET count=0
                      FOR z=1 to 15 step 2
                          IF min(directions(z)+x,directions(z+1)+y)>=1 and max(directions(z)+x,directions(z+1)+y)<=8 then
                             IF sgn(board(directions(z)+x,directions(z+1)+y))=-sgn(board(x,y)) then
                                IF abs(board(directions(z)+x,directions(z+1)+y))>abs(board(x,y)) then
                                   LET count=count+1
                                END IF
                             END IF
                          END IF
                      NEXT z

                      ; Fork found, give bonus if knight is defended or not attacked
                      IF count>1 and (attacked(board(,),x,y,-sgn(board(x,y)))=1 or attacked(board(,),x,y,sgn(board(x,y)))=0) then
                         LET eval=eval+sgn(board(x,y))*0.5
                      END IF

                   ELSEIF abs(board(x,y))=3.1 then    ;bishop
                      IF max(x,y)=8 or min(x,y)=1 then LET eval = eval - sgn(board(x,y)) * 0.25

                   ELSEIF abs(board(x,y))=99 then     ;king
                      IF PieceCounter<6 then
                         LET UseMe=sgn(board(x,y))
                         ; bonus for being in the middle of the board during endgame for losing side
                         IF max(x,y)=7 or min(x,y)=2 then LET KingOnEdge=KingOnEdge+sgn(board(x,y))
                         IF max(x,y)=8 or min(x,y)=1 then LET KingOnEdge=KingOnEdge+2*sgn(board(x,y))
                         IF sgn(board(x,y))=1 then
                            LET wkx=x
                            LET wky=y
                         ELSE
                            LET bkx=x
                            LET bky=y
                         END IF
                         FOR z=17 to 32 step 2   ; look all directions around king for places to move
                             IF max(directions(z)+x,directions(z+1)+y)<=8 and min(directions(z)+x,directions(z+1)+y)>=1 then     ;square is on the board
                                IF sgn(board(directions(z)+x,directions(z+1)+y))=-UseMe then  ;opponent's piece in the way
                                   LET eval=eval - UseMe*.1
                                ELSEIF board(directions(z)+x,directions(z+1)+y)=0 and attacked(board(,),directions(z)+x,directions(z+1)+y,UseMe)=1 then   ; square is attacked
                                   LET eval=eval - UseMe*.1
                                END IF
                             END IF
                         NEXT z

                      END IF

;                      ; penalty for being checked
;                      IF turn = sgn(board(x,y)) and attacked(board(,),x,y,turn)=1 then
;                         LET eval=eval - turn*0.45 ;checked
;                      elseif -turn = sgn(board(x,y)) and attacked(board(,),x,y,turn)=1 then
;                         LET eval=eval - turn*88  ;check, but not turn to move
;                      else
;                      END IF


                      ;king should stay out of the action before the endgame
                      IF PieceCounter>12 then
                         IF board(1,3)=99 or board(1,7)=99 then LET eval=eval+.25
                         IF board(8,3)=-99 or board(8,7)=-99 then LET eval=eval-.25
                         IF x<>1 and  x<>8 then
                            LET eval = eval - sgn(board(x,y)) * 0.25
                         END IF
                      ELSEIF PieceCounter<8 then
                         IF max(x,y)=8 or min(x,y)=1 then LET eval=eval - sgn(board(x,y)) * 0.2

                         ;If piece in front of king is the enemy pawn, give bonus
                         IF y>1 and y<8 and board(x,y+sgn(board(x,y))) = - sgn(board(x,y)) then LET eval=eval + sgn(board(x,y)) * 0.2

                         ;If piece two spaces in front of king is the enemy pawn, give bonus
                         IF y>2 and y<7 and abs(board(x,y+2*sgn(board(x,y)))) = 99 then LET eval=eval + sgn(board(x,y)) * 0.2
                      END IF
                   ELSE
                   END IF
                END IF
            NEXT y
        NEXT x

        IF KingOnEdge<>0 and sgn(KingOnEdge)=-sgn(eval)  then LET eval=eval - KingOnEdge      ; penalty for king being on edge when behind

        IF PieceCounter<5 then LET eval=eval - sgn(eval)* ((abs(wkx-bkx)+abs(wky-bky))/20)    ;penalty for being near other king

        LET eval=eval + 0.5 * eval*(1 - PieceCounter/32)   ; Reward leader for trading down

        LET NumberEvaluated = NumberEvaluated +1

        LET posEval=eval + rnd/10000   ; randomize move among equal values

    END FUNCTION

    ;___________________________________________________________________________________________________


    FUNCTION attacked(board(,),r,c,sign)    ; does not include king attacks
        LOCAL i,x,y,z

        ; check for pawn attacks
        IF   (((sign=1 and r<8 and c<8) or (sign=-1 and r>1 and c<8)) and board(r+sign,c+1)=-sign) or (((sign=1 and r<8 and c>1) or (sign=-1 and r>1 and c>1)) and board(r+sign,c-1)=-sign) then
           LET attacked=1
           EXIT FUNCTION
        END IF

        FOR i=1 to 15 step 2      ; check for knight
            LET x=directions(i)
            LET y=directions(i+1)
            IF min(r+y,c+x)>=1 and max(r+y,c+x)<=8  then
               IF board(r+y,c+x)=-sign*3 then
                  LET attacked=1
                  EXIT FUNCTION
               END IF
            END IF
        NEXT i

        FOR i=17 to 31 step 2
            LET x=directions(i)
            LET y=directions(i+1)

            FOR z=1 to 7          ; distance from piece
                IF min(r+z*y,c+z*x)>=1 and max(r+z*y,c+z*x)<=8 and board(r+z*y,c+z*x)<>0 then
                   ;                   IF z=1 and (board(r+y,c+x)= -sign*99 or board(r+y,c+x)= -sign*9 or (x*y<>0 and board(r+y,c+x)= -sign*3.1) or (x*y=0 and board(r+y,c+x)= -sign*5)) then
                   ;                      LET attacked=1
                   ;                   ELSE
                   IF  board(r+z*y,c+z*x)= -sign*9 or (x*y<>0 and board(r+z*y,c+z*x)= -sign*3.1) or (x*y=0 and board(r+z*y,c+z*x)= -sign*5) then
                      LET attacked=1
                      EXIT FUNCTION
                   ELSE           ;non-attacking piece in direction
                      EXIT FOR
                   END IF
                END IF
            NEXT z
        NEXT i

        LET attacked = 0

    END FUNCTION
    ;___________________________________________________________________________________________________


    SUB pawnmove(row,column,num, board(,),color, move_row, move_column)   ; au passant Not yet implemented
        SELECT CASE row
        CASE 2,7
             SELECT CASE column
             CASE 1 To 8
                  SELECT CASE num
                  CASE 1
                       LET move_row=row+color
                       LET move_column=column
                  CASE 2
                       IF board(row+color,column)=0 then
                          LET move_row=row+2*color
                          IF move_row=9 then LET move_row = 0   ; going wrong direction for 2nd row double push
                          LET move_column=column

                          ; wrong color to move forward 2 on this row (2 or 7)
                       ELSEIF board(row+color,column)<>0 or abs(move_row)=9 then
                          LET move_row=0
                       END IF

                  CASE 3
                       IF column<8 And sgn(board(row+color,column+1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column+1
                       ELSEIF column>1 And sgn(board(row+color,column-1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column-1
                       ELSE
                          LET move_row=0
                       END IF
                  CASE 4
                       IF column>1 And sgn(board(row+color,column-1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column-1
                       ELSEIF column<8 And sgn(board(row+color,column+1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column+1
                       ELSE
                          LET move_row=0
                       END IF

                  CASE Else
                       LET move_row=no_more_moves
                  END SELECT
             END SELECT

        CASE 3 To 6               ; third thru sixth row
             SELECT CASE column
             CASE 1 To 8
                  SELECT CASE num
                  CASE 1
                       LET move_row=row+color
                       LET move_column=column
                  CASE 2
                       IF column<8 And sgn(board(row+color,column+1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column+1
                       ELSEIF column>1 And sgn(board(row+color,column-1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column-1
                       ELSE
                          LET move_row=0
                       END IF
                  CASE 3
                       IF column>1 And sgn(board(row+color,column-1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column-1
                       ELSEIF column<8 And sgn(board(row+color,column+1))=-sgn(board(row,column)) Then
                          LET move_row=row+color
                          LET move_column=column+1
                       ELSE
                          LET move_row=0
                       END IF
                  CASE Else
                       LET move_row=no_more_moves
                  END SELECT
             END SELECT
        CASE else
             LET move_row=no_more_moves
        END SELECT
    END SUB

    ;___________________________________________________________________________________________________


    SUB KingMove(row,column,num,move_row, move_column,board(,), CastleFlag)

        LOCAL IncRow,IncCol       ; Direction to move in (-1 or 0 or 1)

        SELECT CASE num           ;int(num/10)
        CASE 1
             LET IncRow = +1
             LET IncCol = +1
        CASE 2
             LET IncRow = -1
             LET IncCol = -1
        CASE 3
             LET IncRow = +1
             LET IncCol = -1
        CASE 4
             LET IncRow = -1
             LET IncCol = +1
        CASE 5
             LET IncRow = +1
        CASE 6
             LET IncRow = -1
        CASE 7
             LET IncCol = +1
        CASE 8
             LET IncCol = -1
        CASE 9                    ; Castle kingside
             IF row=1 and board(1,5) = 99  and AskCastleFlag(1,8,CastleFlag)=0 then

                IF board(1,6)=0 and board(1,7)=0 and board(1,8)=5 and attacked(board(,),1,5,1)=0 and attacked(board(,),1,6,1)=0 and attacked(board(,),1,7,1)=0 then
                   LET IncCol = +2
                ELSE
                   LET incCol = +10    ; Make move clearly illegal so will be skipped
                END IF
             ELSEIF row=8 and board(8,5) =-99 and AskCastleFlag(8,8,CastleFlag)=0 then
                IF board(8,6)=0 and board(8,7)=0 and board(8,8)=-5 and attacked(board(,),8,5,-1)=0 and attacked(board(,),8,6,-1)=0 and attacked(board(,),8,7,-1)=0 then
                   LET IncCol = +2
                ELSE
                   LET incCol = +10
                END IF
             ELSE
                LET incCol = +10
             END IF
        CASE 10                   ; Castle Queenside
             IF row=1 and board(1,5) = 99 and AskCastleFlag(1,1,CastleFlag)=0 then
                IF board(1,4)=0 and board(1,3)=0 and board(1,2)=0 and board(1,1)=5 and attacked(board(,),1,5,1)=0 and attacked(board(,),1,4,1)=0 and attacked(board(,),1,3,1)=0 then
                   LET IncCol = -2
                ELSE
                   LET incCol = +10    ; Make move clearly illegal so will be skipped
                END IF
             ELSEIF row=8 and board(8,5) =-99 and AskCastleFlag(8,1,CastleFlag)=0 then
                IF board(8,4)=0 and board(8,3)=0 and board(8,2)=0  and board(8,1)=-5 and attacked(board(,),8,5,-1)=0 and attacked(board(,),8,4,-1)=0 and attacked(board(,),8,3,-1)=0 then
                   LET IncCol = -2
                ELSE
                   LET incCol = +10
                END IF
             ELSE
                LET incCol = +10
             END IF
        CASE 11
             LET move_row=no_more_moves
             EXIT SUB
        END SELECT

        LET move_row    = row    + IncRow
        LET move_column = column + IncCol

        IF move_row<1 or move_column<1 or max(move_row,move_column)>8 then  LET move_row=0    ; off the board, skip

    END SUB

    ;___________________________________________________________________________________________________


    SUB KnightMove(row,column,num,move_row, move_column)
        SELECT CASE num
        CASE 1
             LET move_row=   row    -2
             LET move_column=column -1
        CASE 2
             LET move_row=   row    -2
             LET move_column=column +1
        CASE 3
             LET move_row=   row    -1
             LET move_column=column -2
        CASE 4
             LET move_row=   row    -1
             LET move_column=column +2
        CASE 5
             LET move_row=   row    +1
             LET move_column=column -2
        CASE 6
             LET move_row=   row    +1
             LET move_column=column +2
        CASE 7
             LET move_row=   row    +2
             LET move_column=column -1
        CASE 8
             LET move_row=   row    +2
             LET move_column=column +1
        CASE Else
             LET move_row=no_more_moves
             EXIT SUB
        END SELECT

        ; move is outside the board, then move_row = 0 (invalid move)
        IF move_row<1 or move_column<1 or max(move_row,move_column)>8 then    LET move_row=0
    END SUB

    ;___________________________________________________________________________________________________

    SUB RookMove(row,column,num,move_row, move_column, board(,),CastleFlag)
        LOCAL IncRow,IncCol       ; Direction to move in (-1 or 0 or 1)
        LOCAL NumSquares          ; Number of squares to move

        LET NumSquares = num - int(num/10)*10    ; first digit of num is direction of move, second tells how far

        SELECT CASE int(num/10)
        CASE 0
             LET IncRow = +1
        CASE 1
             LET IncRow = -1
        CASE 2
             LET IncCol = +1
        CASE 3
             LET IncCol = -1
        CASE 4
             LET move_row=no_more_moves
             EXIT SUB
        END SELECT

        LET move_row    = row    + IncRow * NumSquares
        LET move_column = column + IncCol * NumSquares

        IF move_row<1 or move_column<1 or max(move_row,move_column)>8 then
           LET move_row=0         ; off the board, skip
           LET num=int(num/10)*10+10   ; ... and change direction
        ELSEIF board(move_row,move_column)<>0 then
           LET num=int(num/10)*10+10   ; piece encountered, so stop looking in current direction
        ELSE
        END IF

    END SUB

    ;___________________________________________________________________________________________________

    SUB BishopMove(row,column,num,move_row, move_column, board(,))
        LOCAL IncRow,IncCol       ; Direction to move in (-1 or 0 or 1)
        LOCAL NumSquares          ; Number of squares to move

        LET NumSquares = num - int(num/10)*10    ; first digit of num is direction of move, second tells how far

        SELECT CASE int(num/10)
        CASE 0
             LET IncRow = +1
             LET IncCol = +1
        CASE 1
             LET IncRow = -1
             LET IncCol = -1
        CASE 2
             LET IncRow = +1
             LET IncCol = -1
        CASE 3
             LET IncRow = -1
             LET IncCol = +1
        CASE 4
             LET move_row=no_more_moves
             EXIT SUB
        END SELECT

        LET move_row    = row    + IncRow * NumSquares
        LET move_column = column + IncCol * NumSquares

        IF move_row<1 or move_column<1 or max(move_row,move_column)>8 then
           LET move_row=0         ; off the board, skip
           LET num=int(num/10)*10+10   ; ... and change direction
        ELSEIF board(move_row,move_column)<>0 then
           LET num=int(num/10)*10+10   ; piece encountered, so stop looking in current direction
        ELSE
        END IF


    END SUB


    ;___________________________________________________________________________________________________
    SUB QueenMove(row,column,num,move_row, move_column, board(,))
        LOCAL IncRow,IncCol       ; Direction to move in (-1 or 0 or 1)
        LOCAL NumSquares          ; Number of squares to move

        LET NumSquares = num - int(num/10)*10    ; first digit of num is direction of move, second tells how far

        SELECT CASE int(num/10)
        CASE 0
             LET IncRow = +1
             LET IncCol = +1
        CASE 1
             LET IncRow = -1
             LET IncCol = -1
        CASE 2
             LET IncRow = +1
             LET IncCol = -1
        CASE 3
             LET IncRow = -1
             LET IncCol = +1
        CASE 4
             LET IncRow = +1
        CASE 5
             LET IncRow = -1
        CASE 6
             LET IncCol = +1
        CASE 7
             LET IncCol = -1
        CASE 8
             LET move_row=no_more_moves
             EXIT SUB
        END SELECT

        LET move_row    = row    + IncRow * NumSquares
        LET move_column = column + IncCol * NumSquares

        IF move_row<1 or move_column<1 or max(move_row,move_column)>8 then
           LET move_row=0         ; off the board, skip
           LET num=int(num/10)*10+10   ; ... and change direction
        ELSEIF board(move_row,move_column)<>0 then
           LET num=int(num/10)*10+10   ; piece encountered, so stop looking in current direction
        ELSE
        END IF

    END SUB


    ;___________________________________________________________________________________________________




    SUB setupboard(board(,))      ; just pawns and king for now
        LOCAL x
        MAT board=zer(1 To 8, 1 To 8)
        FOR x =1 To 8
            LET board(2,x) = 1    ; White pawn
            LET board(7,x) = -1   ; Black pawn
        NEXT x

        LET board(1,1) = 5        ;w rook
        LET board(1,2) = 3        ;w knight
        LET board(1,3) = 3.1      ;w bishop
        LET board(1,4) = 9        ;w queen
        LET board(1,5) = 99       ;w king
        LET board(1,6) = 3.1      ;w bishop
        LET board(1,7) = 3        ;w knight
        LET board(1,8) = 5        ;w rook

        LET board(8,1)=-5         ; b rook
        LET board(8,2)=-3         ; b knight
        LET board(8,3)=-3.1       ; b bishop
        LET board(8,4)=-9         ; b queen
        LET board(8,5)=-99        ; b king
        LET board(8,6)=-3.1       ; b bishop
        LET board(8,7)=-3         ; b knight
        LET board(8,8)=-5         ; b rook

    END SUB

END SUB


;___________________________________________________________________________________________________

SUB printboard(board(,))
    LOCAL x,y
    CLEAR
    SET BACK "black"
    FOR x=8 To 1 Step -1
        SET COLOR "white"
        PRINT x;" ";
        FOR y=1 To 8
            IF sgn(board(x,y))>0 then
               SET COLOR "red"
            ELSEIF sgn(board(x,y))<0  then
               SET COLOR "yellow"
            ELSE
               SET COLOR "green"
            END IF
            SELECT CASE board(x,y)
            CASE 0
                 IF mod(y+x,2)=0 then PRINT " "&chr$(250); else PRINT " "&chr$(249);
            CASE 1
                 PRINT " P";
            CASE -1
                 PRINT " p";
            CASE 3
                 PRINT " N";
            CASE -3
                 PRINT " n";
            CASE 3.1
                 PRINT " B";
            CASE -3.1
                 PRINT " b";
            CASE 5
                 PRINT " R";
            CASE -5
                 PRINT " r";
            CASE 9
                 PRINT " Q";
            CASE -9
                 PRINT " q";
            CASE 99
                 PRINT " K";
            CASE -99
                 PRINT " k";
            END SELECT
        NEXT y
        PRINT
    NEXT x
    SET COLOR "black"
    PRINT ""
    PRINT "     A B C D E F G H"

END SUB

SUB drawboard(board(,),BoardPic$,BlackSquare$,WhiteSquare$)
    LOCAL colstr$,x,y
    SET BACK "black"
    SET COLOR "white"
    CLEAR


    LET colstr$="abcdefgh"

    IF BoardPic$="" then

       FOR x = 1 to 9             ; Board
           PLOT x,1;x,9
           PLOT 1,x;9,x
       NEXT x

       FOR y=1 to 8
           SET COLOR "cyan"
           PLOT TEXT, AT y+.5,.5: colstr$[y:y]   ; type letter coordinates
           FOR x=1 to 8
               SET COLOR "cyan"
               PLOT TEXT, AT .5,x+.5: str$(x)    ; type number coordinates
               IF mod(x+y,2)=0 then
                  ;                  SET COLOR "brown"    ; fill every other square
                  SET COLOR MIX (20) .3,.3,.3
                  SET COLOR 20
               ELSE
                  SET COLOR "white"    ; fill every other square
               END IF
               FLOOD x+.5,y+.5
           NEXT x
       NEXT y
       BOX KEEP 0,9,0,9 in BoardPic$
       BOX KEEP 1,2,1,2 in BlackSquare$
       BOX KEEP 2,3,1,2 in WhiteSquare$
    ELSE
       BOX SHOW boardpic$ at 0,0
    END IF

    FOR y=1 to 8
        FOR x=1 to 8
            SELECT CASE board(x,y)
            CASE 0
            CASE 1
                 DRAW WhitePawn with shift(y,x)
            CASE -1
                 DRAW BlackPawn with shift(y,x)
            CASE 3
                 DRAW WhiteKnight with shift(y,x)
            CASE -3
                 DRAW BlackKnight with shift(y,x)
            CASE 3.1
                 DRAW WhiteBishop with shift(y,x)
            CASE -3.1
                 DRAW BlackBishop with shift(y,x)
            CASE 5
                 DRAW WhiteRook with shift(y,x)
            CASE -5
                 DRAW BlackRook with shift(y,x)
            CASE 9
                 DRAW WhiteQueen with shift(y,x)
            CASE -9
                 DRAW BlackQueen with shift(y,x)
            CASE 99
                 DRAW WhiteKing with shift(y,x)
            CASE -99
                 DRAW BlackKing with shift(y,x)
            END SELECT
        NEXT x
    NEXT y

END SUB


;___________________________________________________________________________________________________



PICTURE WhiteRook
    SET COLOR "Green"
    PLOT .2,.1; .8,.1; .7,.2;
    PLOT .7,.25; .7,.3; .7,.8;
    PLOT .3,.8; .3,.3; .3,.2; .2,.1
    PLOT .42,.8; .42,.74; .45,.74; .45,.8
    PLOT .58,.8; .58,.74; .55,.74; .55,.8

    SET COLOR "yellow"
    FLOOD .5,.5

END PICTURE

PICTURE BlackRook
    SET COLOR "Green"
    PLOT .2,.1; .8,.1; .7,.2;
    PLOT .7,.25; .7,.3; .7,.8;
    PLOT .3,.8; .3,.3; .3,.2; .2,.1
    PLOT .42,.8; .42,.74; .45,.74; .45,.8
    PLOT .58,.8; .58,.74; .55,.74; .55,.8

    SET COLOR "Black"
    FLOOD .5,.5

END PICTURE


PICTURE WhiteKnight
    SET COLOR "Green"
    PLOT .2,.1;.8,.1;.8,.2;
    PLOT .7,.25;.7,.3;.8,.4;.65,.7;.6,.9;.55,.9;
    PLOT .5,.82;.2,.75;.2,.6;.3,.6;.4,.55;
    PLOT .25,.45;.2,.37;.3,.3;.3,.25;.2,.2;.2,.1
    SET COLOR "yellow"
    FLOOD .5,.5

END PICTURE


PICTURE BlackKnight
    SET COLOR "Green"
    PLOT .2,.1;.8,.1;.8,.2;
    PLOT .7,.25;.7,.3;.8,.4;.65,.7;.6,.9;.55,.9;
    PLOT .5,.82;.2,.75;.2,.6;.3,.6;.4,.55;
    PLOT .25,.45;.2,.37;.3,.3;.3,.25;.2,.2;.2,.1
    SET COLOR "Black"
    FLOOD .5,.5

END PICTURE

PICTURE WhitePawn
    SET COLOR "Green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .63,.35; .65,.55;
    PLOT .60,.57; .55,.60; .45,.60; .40,.57;
    PLOT .37,.55;.39,.35; .39,.2; .2,.1

    SET COLOR "yellow"
    FLOOD .5,.5

END PICTURE

PICTURE Blackpawn
    SET COLOR "green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .63,.35; .65,.55;
    PLOT .60,.57; .55,.60; .45,.60; .40,.57;
    PLOT .37,.55;.39,.35; .39,.2; .2,.1

    SET COLOR "black"
    FLOOD .5,.5

END PICTURE

PICTURE WhiteBishop
    SET COLOR "Green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .63,.35; .65,.65;
    PLOT .60,.67; .55,.76; .45,.76;.40,.67;
    PLOT .37,.65;.39,.35; .39,.2; .2,.1
    PLOT .60,.67; .52,.52; .55,.52; .62,.69
    SET COLOR "Yellow"
    FLOOD .5,.3

END PICTURE

PICTURE BlackBishop
    SET COLOR "green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .63,.35; .65,.65;
    PLOT .60,.67; .55,.76; .45,.76;.40,.67;
    PLOT .37,.65;.39,.35; .39,.2; .2,.1
    SET COLOR "Black"
    FLOOD .5,.5
    SET COLOR "yellow"
    PLOT .60,.67; .52,.52; .55,.52; .62,.69

END PICTURE

PICTURE WhiteKing
    SET COLOR "green"
    PLOT .2,.1; .8,.1;  .61,.55; .55,.60;
    PLOT .55,.73;.8,.73;.8,.78;.55,.78;.55,1;
    PLOT .45,1;.45,.78;.2,.78; .2,.73; .45,.73; .45,.60;
    PLOT .39,.55;  .2,.1

    SET COLOR "yellow"
    FLOOD .53,.77
    FLOOD .5,.5

END PICTURE

PICTURE BlackKing
    SET COLOR "green"
    PLOT .2,.1; .8,.1;  .61,.55; .55,.60;
    PLOT .55,.73;.8,.73;.8,.78;.55,.78;.55,1;
    PLOT .45,1;.45,.78;.2,.78; .2,.73; .45,.73; .45,.60;
    PLOT .39,.55;  .2,.1

    SET COLOR "black"
    FLOOD .5,.5

END PICTURE


PICTURE WhiteQueen
    SET COLOR "Green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .8,.8; .66,.66; .5,1; .33,.66; .2,.8;
    PLOT .39,.2; .2,.1

    SET COLOR "yellow"
    FLOOD .5,.5

END PICTURE



PICTURE BlackQueen
    SET COLOR "green"
    PLOT .2,.1; .8,.1; .63,.2;
    PLOT .8,.8; .66,.66; .5,1; .33,.66; .2,.8;
    PLOT .39,.2; .2,.1

    SET COLOR "black"
    FLOOD .5,.5

END PICTURE


;___________________________________________________________________________________________________


SUB MovePics(FromRow,FromCol,ToRow,ToCol,BlackSquare$,WhiteSquare$,piece)

    IF mod(FromCol+FromRow,2)=1 then
       BOX SHOW WhiteSquare$ at FromCol,FromRow
    ELSE
       BOX SHOW BlackSquare$ at FromCol,FromRow
    END IF

    IF mod(ToRow+ToCol,2)=1 then
       BOX SHOW WhiteSquare$ at ToCol,ToRow
    ELSE
       BOX SHOW BlackSquare$ at ToCol,ToRow
    END IF

    SELECT CASE piece
    CASE 0
    CASE 1
         DRAW WhitePawn with shift(ToCol,ToRow)
    CASE -1
         DRAW BlackPawn with shift(ToCol,ToRow)
    CASE 3
         DRAW WhiteKnight with shift(ToCol,ToRow)
    CASE -3
         DRAW BlackKnight with shift(ToCol,ToRow)
    CASE 3.1
         DRAW WhiteBishop with shift(ToCol,ToRow)
    CASE -3.1
         DRAW BlackBishop with shift(ToCol,ToRow)
    CASE 5
         DRAW WhiteRook with shift(ToCol,ToRow)
    CASE -5
         DRAW BlackRook with shift(ToCol,ToRow)
    CASE 9
         DRAW WhiteQueen with shift(ToCol,ToRow)
    CASE -9
         DRAW BlackQueen with shift(ToCol,ToRow)
    CASE 99
         DRAW WhiteKing with shift(ToCol,ToRow)
    CASE -99
         DRAW BlackKing with shift(ToCol,ToRow)
    END SELECT
END SUB


;___________________________________________________________________________________________________

SUB SetCastleFlag(x,y,CastleFlag)
    LOCAL tmp
    SELECT CASE x                 ; Each castling piece is assigned a prime number flag
    CASE 1                        ; When a peice is moved, the flags are set by multiplying
         SELECT CASE y            ; the pieces prime number by the other CastleFlags
         CASE 1
              LET tmp=2
         CASE 5
              LET tmp=2*3         ; any king move sets all flags for side
         CASE 8
              LET tmp=3
         CASE else
         END SELECT
    CASE 8
         SELECT CASE y
         CASE 1
              LET tmp=5
         CASE 5
              LET tmp=5*7
         CASE 8
              LET tmp=7
         CASE else
         END SELECT
    CASE else
    END SELECT
    LET CastleFlag=tmp*CastleFlag
END SUB

;___________________________________________________________________________________________________

FUNCTION AskCastleFlag(x,y,CastleFlag)
    LOCAL divisor
    SELECT CASE x
    CASE 1
         SELECT CASE y
         CASE 1
              LET divisor=2
         CASE 5
              LET divisor=2*3
         CASE 8
              LET divisor=3
         CASE ELSE
              LET divisor=1
         END SELECT
    CASE 8
         SELECT CASE y
         CASE 1
              LET divisor=5
         CASE 5
              LET divisor=5*7
         CASE 8
              LET divisor=7
         CASE ELSE
              LET divisor=1
         END SELECT
    END SELECT

    ; if divisor divides evenly into CastleFlag, then flag was set
    IF CastleFlag<>1 and mod(CastleFlag,divisor)=0 then
       LET AskCastleFlag=1
    ELSE
       LET AskCastleFlag=0
    END IF
END FUNCTION



;___________________________________________________________________________________________________


SUB info(BestFromR(),BestFromC(),BestToR(),BestToC(),NumberEvaluated,besteval,note$,MaxPlyLevel)
    LOCAL MaxRow,MaxCol,colstr$,x
    LET colstr$="abcdefgh"
    ASK MAX CURSOR MaxRow,MaxCol

    SET BACK "black"
    SET COLOR "white"

    SET CURSOR MaxRow-5,1
    PRINT
    IF note$<>"" then
       PRINT note$
    ELSE
       FOR x=MaxPlyLevel to 1 step -1
           PRINT colstr$[BestFromC(x):BestFromC(x)]&str$(BestFromR(x))&colstr$[BestToC(x):BestToC(x)]&str$(BestToR(x));"         ";
       NEXT x
    END IF
    PRINT "       "
    PRINT "your score = ";
    IF abs(besteval)<9999 then  PRINT round(besteval*10)/10;"    " else PRINT "     "
    PRINT "Positions Evaluated = ";NumberEvaluated
END SUB

FUNCTION Notate$(FromR,FromC,ToR,ToC)
    LOCAL colstr$
    LET colstr$="abcdefgh"
    LET Notate$=colstr$[FromC:FromC]&trim$(str$(FromR))&colstr$[ToC:ToC]&trim$(str$(ToR))
END FUNCTION

SUB resign
    LOCAL x,y,a,b,c
    ASK CURSOR x,y
    SOUND 1000,0.1
    FOR a=1 to 30
        SET CURSOR x,y
        IF mod(a,2)=0 then  SET COLOR "yellow" else SET COLOR "cyan"
        PRINT "*** I resign ***"
        IF key input then STOP
        PAUSE .2
    NEXT a
    STOP
END SUB



Knotz(Posted 2004) [#9]
There is a mexican fellow(Alejandro Migoya) selling a chess engine made is VB for $30. Convert it (and fix it) and you you have a working chess engine.


Rook Zimbabwe(Posted 2004) [#10]
I have a few examples in VB... I am lousy at converting stuff... touch of Dyslexia... :]

Wayne... I am going to play with that code. Hmmm...

I already looked at an othello engine and simple AI. Have the code. Seems silly sometimes... looks first for the corners and then at the edges and then randomly in the middle... Still also interesting.

All interesting. Learning muchly now. Oy! :]

posting abut my othello prob soon.

_rz


Wayne(Posted 2004) [#11]
Keep at it you'll figure that stuff out, I did.
8)