Also see the KIM-1 Software page for the binary exact source of Microchess.
Many years ago, when a 6502 and a few k or RAM were cutting edge in home computing, I tried, and failed, to get the KIM version of Microchess to run on my Compukit UK101.
I recently found the source and, in a fit of nostalgia, made this version which runs on Michal Kowalski’s.
This version is posted with the permission of Peter Jennings.
The program
Once you have the source (see later) you will need to load it into the simulator, assemble it, and the run it in the debugger.
The game
Notation
Each square on the chess board is identified by a two digit number as shown here. The first digit specifies the rank (0x to 7x) from the computer’s end of the board. The second digit specifies the file (x0 to x7) from the player’s left. Moves are made by the FROM square and the TO square using this notation.
Command keys
Few keys are needed to play. The original KIM had only a hex kaypad and a few command keys. This version has code to interpret standard ASCII codes in their place. Alpha keys can be used in either upper or lower case, both have the same effect.
[C] | This key [C]lears the internal chessboard and resets it to begin another game. The board is set up with the computer playing white. ‘? Reset 00 00‘ is displayed instead of a move to indicate that the board has been reset. |
[E] | This key [E]xchanges the two sets of pieces without the actual position of the board being changed. ‘? Exchange 00 00‘ is displayed instead of a move to indicate that the exchange has been made. If [C] then [E] is pressed, the board will be set up to begin a game with the computer playing black. If [P] followed by [E] followed by [P], and so on, is pressed the computer will play a game against itself. |
[P] | This key tells the computer to [P]lay its move. While the computer decides on the best move it will flash the ‘?’ character on the move line and, sometimes, display the move it’s deciding on. |
[ENTER] | This key is used to register the player’s move. It moves the piece on the FROM square to the TO square. This can be used to move one of the computer’s men if desired. |
Your moves are entered into the game numerically using the notation described above. You do not enter piece being moved, just the FROM and TO square locations.
As move numbers are entered they scroll from right to left through the TO and FROM digits, the FROM square piece is updated after every key. Should you make an error while entering the move just re-enter the move and the display will scroll to the left until the correct move is displayed.
While you are entering your move the piece located on the FROM square is displayed on the left of the status line after the ‘?‘ character. There is no indication of the pieces colour, it is up to you to move only your own pieces.
When you are sure the move you’ve entered is the correct one press the [ENTER] key to register the move on the board. Once you have pressed [ENTER] the display confirms the move by showing the piece now in the TO square and the FROM and TO squares.
You may make as many moves like this as you wish and may move either your own men or the computer’s. No check on the legality of the move is carried out. Illegal moves will be executed just as legal moves, so you should be carefull that you do not accidentally make an illegal move. There is no warning if your king is in check, you must be careful not to leave this situation after your move. If you do the computer will usually take your king on its next move if possible.
The source.
The source is changed from the original source to use the ASCII input/output of the simulator. This roughly follows the suggestions in the KIM MicroChess programmers manual on teletype I/O.
Where code has been added it has lower case comments and where code has been changed the original code has usually been commented out, but otherwise left in place. The main strategy and computer play routines are essentially unchanged from the original.
The OCRed source that I worked from had some transcription errors. Though I found and corrected some, others may remain.
You can either view the source as html or download the source as a zip archive.
; MicroChess (c) 1976-2002 Peter Jennings, peterj@benlo.com ; this version for the integrated macroassembler, simulator and debugger for ; 650x microprocessor family by Michal Kowalski ; additions and changes by Lee Davison ; from suggested ASCII routines in the KIM MicroChess programmers notes ; this version is posted with the permission of Peter Jennings ; display flash during compute move replaced by '?' prompt flash ; piece display changed to display piece at 'to' square after each move ; Simulator I/O base addresse is $F000 ; Simulator window size is 64 columns x 20 rows IO_AREA = $F000 ACIAsimwr = IO_AREA+$01 ACIAsimrd = IO_AREA+$04 DispPosX = IO_AREA+$05 DispPosY = IO_AREA+$06 ; page zero variables BOARD = $50 BK = $60 PIECE = $B0 SQUARE = $B1 SP2 = $B2 SP1 = $B3 INCHEK = $B4 STATE = $B5 MOVEN = $B6 OMOVE = $DC WCAP0 = $DD COUNT = $DE BCAP2 = $DE WCAP2 = $DF BCAP1 = $E0 WCAP1 = $E1 BCAP0 = $E2 MOB = $E3 MAXC = $E4 CC = $E5 PCAP = $E6 BMOB = $E3 BMAXC = $E4 _BCC = $E5 ; was BCC BMAXP = $E6 XMAXC = $E8 WMOB = $EB WMAXC = $EC WCC = $ED WMAXP = $EE PMOB = $EF PMAXC = $F0 PCC = $F1 PCP = $F2 OLDKY = $F3 BESTP = $FB BESTV = $FA BESTM = $F9 DIS1 = $FB DIS2 = $FA DIS3 = $F9 prompt = $FC ; prompt character, '?' or ' ' reverse = $FD ; which way round is the display board *=$1000 ; load into RAM @ $1000 onwards CHESS CLD ; INITIALIZE LDX #$FF ; TWO STACKS TXS LDX #$C8 STX SP2 ; ROUTINES TO LIGHT LED ; DISPLAY AND GET KEY ; FROM KEYBOARD OUT JSR DrawBoard ; draw board LDA #'?' ; prompt character STA prompt ; save it GetKey JSR UpdateDisp ; update prompt & display JSR asciiin ; get key press CMP #'C' ; is it C BNE NOSET ; branch if not ; else set up board LDX #$1F ; 32 pieces to do WHSET LDA SETW,X ; FROM STA BOARD,X ; SETW DEX BPL WHSET LDA #$00 ; no reverse STA reverse ; set it LDX #$1B ; *ADDED STX OMOVE ; INITS TO $FF LDA #$CC ; Display CCC BNE CLDSP NOSET CMP #'E' ; [E] BNE NOREV ; REVERSE JSR REVERSE ; BOARD IS LDA reverse ; get reversed flag EOR #$01 ; toggle reverse bit STA reverse ; save flag LDA #$EE ; IS BNE CLDSP NOREV CMP #'P' ; [P] BNE NOGO ; PLAY CHESS JSR GO CLDSP STA DIS1 ; DISPLAY LDA #$00 STA DIS2 ; ACROSS STA DIS3 ; DISPLAY BEQ CHESS NOGO CMP #$0D ; [Enter] BNE NOMV ; MOVE MAN JSR MOVE ; AS ENTERED ; JSR DISP2 ; piece into display JSR DISP3 ; piece into display JMP CHESS ; main loop NOMV ; CMP #'Q' ; [Q] ***Added to allow game exit*** ; BEQ DONE ; quit the game, exit back to system. ; removed from simulator version as no system! JMP INPUT ; process move ;DONE ; JMP $FF00 ; *** MUST set this to YOUR OS starting address ; THE ROUTINE JANUS DIRECTS THE ; ANALYSIS BY DETERMINING WHAT ; SHOULD OCCUR AFTER EACH MOVE ; GENERATED BY GNM JANUS LDX STATE BMI NOCOUNT ; THIS ROUTINE COUNTS OCCURRENCES ; IT DEPENDS UPON STATE TO INDEX ; THE CORRECT COUNTERS COUNTS LDA PIECE BEQ OVER ; IF STATE=8 CPX #$08 ; DO NOT COUNT BNE OVER ; BLK MAX CAP CMP BMAXP ; MOVES FOR BEQ XRT ; WHITE OVER INC MOB,X ; MOBILITY CMP #$01 ; + QUEEN BNE NOQ ; FOR TWO INC MOB,X NOQ BVC NOCAP LDY #$0F ; CALCULATE LDA SQUARE ; POINTS ELOOP CMP BK,Y ; CAPTURED BEQ FOUN ; BY THIS DEY ; MOVE BPL ELOOP FOUN LDA POINTS,Y CMP MAXC,X BCC LESS ; SAVE IF STY PCAP,X ; BEST THIS STA MAXC,X ; STATE LESS CLC PHP ; ADD TO ADC CC,X ; CAPTURE STA CC,X ; COUNTS PLP NOCAP CPX #$04 BEQ ON4 BMI TREE ; (=00 ONLY) XRT RTS ; GENERATE FURTHER MOVES FOR COUNT ; AND ANALYSIS ON4 LDA XMAXC ; SAVE ACTUAL STA WCAP0 ; CAPTURE LDA #$00 ; STATE=0 STA STATE JSR MOVE ; GENERATE JSR REVERSE ; IMMEDIATE JSR GNMZ ; REPLY MOVES JSR REVERSE LDA #$08 ; STATE=8 STA STATE ; GENERATE JSR GNM ; CONTINUATION JSR UMOVE ; MOVES JMP STRATGY ; FINAL EVALUATION NOCOUNT CPX #$F9 BNE TREE ; DETERMINE IF THE KING CAN BE ; TAKEN, USED BY CHKCHK LDA BK ; IS KING CMP SQUARE ; IN CHECK? BNE RETJ ; SET INCHEK=0 LDA #$00 ; IF IT IS STA INCHEK RETJ RTS ; IF A PIECE HAS BEEN CAPTURED BY ; A TRIAL MOVE, GENERATE REPLIES & ; EVALUATE THE EXCHANGE GAIN/LOSS TREE BVC RETJ ; NO CAP LDY #$07 ; (PIECES) LDA SQUARE LOOPX CMP BK,Y BEQ FOUNX DEY BEQ RETJ ; (KING) BPL LOOPX ; SAVE FOUNX LDA POINTS,Y ; BEST CAP CMP BCAP0,X ; AT THIS BCC NOMAX ; LEVEL STA BCAP0,X NOMAX DEC STATE LDA #$FB ; IF STATE=FB CMP STATE ; TIME TO TURN BEQ UPTREE ; AROUND JSR GENRM ; GENERATE FURTHER UPTREE INC STATE ; CAPTURES RTS ; THE PLAYER'S MOVE IS INPUT INPUT SEC ; set for subtract SBC #'0' ; convert ASCII # to binary CMP #$08 ; NOT A LEGAL BCS ERROR ; SQUARE # JSR DISMV JSR DISP2 ; put piece into display ERROR JMP GetKey ; go update move display and wait for next key ; JMP CHESS DISP3 LDA DIS3 ; get position .byte $2C ; make next LDA into BIT xxxx DISP2 LDA DIS2 ; get position LDX #$1F SEARCH CMP BOARD,X ; compare with this piece's position ; LDA BOARD,X ; CMP DIS2 BEQ HERE ; DISPLAY DEX ; PIECE AT BPL SEARCH ; FROM LDX #$BB ; blank square if no matching piece HERE STX DIS1 ; SQUARE STX PIECE RTS ; GENERATE ALL MOVES FOR ONE ; SIDE, CALL JANUS AFTER EACH ; ONE FOR NEXT STE? GNMZ LDX #$10 ; CLEAR GNMX LDA #$00 ; COUNTERS CLEAR STA COUNT,X DEX BPL CLEAR GNM LDA #$10 ; SET UP STA PIECE ; PIECE NEWP DEC PIECE ; NEW PIECE BPL NEX ; ALL DONE? RTS ; #NAME? NEX JSR RESET ; READY LDY PIECE ; GET PIECE LDX #$08 STX MOVEN ; COMMON START CPY #$08 ; WHAT IS IT? BPL PAWN ; PAWN CPY #$06 BPL KNIGHT ; KNIGHT CPY #$04 BPL BISHOP ; BISHOP CPY #$01 BEQ QUEEN ; QUEEN BPL ROOK ; ROOK KING JSR SNGMV ; MUST BE KING! BNE KING ; MOVES BEQ NEWP ; 8 TO 1 QUEEN JSR LINE BNE QUEEN ; MOVES BEQ NEWP ; 8 TO 1 ROOK LDX #$04 STX MOVEN ; MOVES AGNR JSR LINE ; 4 TO 1 BNE AGNR BEQ NEWP BISHOP JSR LINE LDA MOVEN ; MOVES CMP #$04 ; 8 TO 5 BNE BISHOP BEQ NEWP KNIGHT LDX #$10 STX MOVEN ; MOVES AGNN JSR SNGMV ; 16 TO 9 LDA MOVEN CMP #$08 BNE AGNN BEQ NEWP PAWN LDX #$06 STX MOVEN P1 JSR CMOVE ; RIGHT CAP? BVC P2 BMI P2 JSR JANUS ; YES P2 JSR RESET DEC MOVEN ; LEFT CAP? LDA MOVEN CMP #$05 BEQ P1 P3 JSR CMOVE ; AHEAD BVS NEWP ; ILLEGAL BMI NEWP JSR JANUS LDA SQUARE ; GETS TO AND #$F0 ; 3RD RANK? CMP #$20 BEQ P3 ; DO DOUBLE JMP NEWP ; CALCULATE SINGLE STEP MOVES ; FOR K,N SNGMV JSR CMOVE ; CALC MOVE BMI ILL1 ; -IF LEGAL JSR JANUS ; -EVALUATE ILL1 JSR RESET DEC MOVEN RTS ; CALCULATE ALL MOVES DOWN A ; STRAIGHT LINE FOR Q,B,R LINE JSR CMOVE ; CALC MOVE BCC OVL ; NO CHK BVC LINE ; NOCAP OVL BMI ILL ; RETURN PHP JSR JANUS ; EVALUATE POSN PLP BVC LINE ; NOT A CAP ILL JSR RESET ; LINE STOPPED DEC MOVEN ; NEXT DIR RTS ; EXCHANGE SIDES FOR REPLY ; ANALYSIS REVERSE LDX #$0F ETC SEC LDY BK,X ; SUBTRACT LDA #$77 ; POSITION SBC BOARD,X ; FROM 77 STA BK,X STY BOARD,X ; AND SEC LDA #$77 ; EXCHANGE SBC BOARD,X ; PIECES STA BOARD,X DEX BPL ETC RTS ; CMOVE CALCULATES THE TO SQUARE ; USING SQUARE AND THE MOVE ; TABLE FLAGS SET AS FOLLOWS: ; N#NAME? MOVE ; V#NAME? (LEGAL UNLESS IN CR) ; C#NAME? BECAUSE OF CHECK ; [MY &THANKS TO JIM BUTTERFIELD ; WHO WROTE THIS MORE EFFICIENT ; VERSION OF CMOVE) CMOVE LDA SQUARE ; GET SQUARE LDX MOVEN ; MOVE POINTER CLC ADC MOVEX,X ; MOVE LIST STA SQUARE ; NEW POS'N AND #$88 BNE ILLEGAL ; OFF BOARD LDA SQUARE LDX #$20 LOOP DEX ; IS TO BMI NO ; SQUARE CMP BOARD,X ; OCCUPIED? BNE LOOP CPX #$10 ; BY SELF? BMI ILLEGAL LDA #$7F ; MUST BE CAP! ADC #$01 ; SET V FLAG BVS SPX ; (JMP) NO CLV ; NO CAPTURE SPX LDA STATE ; SHOULD WE BMI RETL ; DO THE CMP #$08 ; CHECK CHECK? BPL RETL ; CHKCHK REVERSES SIDES ; AND LOOKS FOR A KING ; CAPTURE TO INDICATE ; ILLEGAL MOVE BECAUSE OF ; CHECK SINCE THIS IS ; TIME CONSUMING, IT IS NOT ; ALWAYS DONE CHKCHK PHA ; STATE #392 PHP LDA #$F9 STA STATE ; GENERATE STA INCHEK ; ALL REPLY JSR MOVE ; MOVES TO JSR REVERSE ; SEE IF KING JSR GNM ; IS IN JSR RUM ; CHECK PLP PLA STA STATE LDA INCHEK BMI RETL ; NO - SAFE SEC ; YES - IN CHK LDA #$FF RTS RETL CLC ; LEGAL LDA #$00 ; RETURN RTS ILLEGAL LDA #$FF CLC ; ILLEGAL CLV ; RETURN RTS ; REPLACE PIECE ON CORRECT SQUARE RESET LDX PIECE ; GET LOGAT LDA BOARD,X ; FOR PIECE STA SQUARE ; FROM BOARD RTS GENRM JSR MOVE ; MAKE MOVE GENR2 JSR REVERSE ; REVERSE BOARD JSR GNM ; GENERATE MOVES RUM JSR REVERSE ; REVERSE BACK ; ROUTINE TO UNMAKE A MOVE MADE BY ; MOVE UMOVE TSX ; UNMAKE MOVE STX SP1 LDX SP2 ; EXCHANGE TXS ; STACKS PLA ; MOVEN STA MOVEN PLA ; CAPTURED STA PIECE ; PIECE TAX PLA ; FROM SQUARE STA BOARD,X PLA ; PIECE TAX PLA ; TO SOUARE STA SQUARE STA BOARD,X JMP STRV ; THIS ROUTINE MOVES PIECE ; TO SQUARE, PARAMETERS ; ARE SAVED IN A STACK TO UNMAKE ; THE MOVE LATER MOVE TSX STX SP1 ; SWITCH LDX SP2 ; STACKS TXS LDA SQUARE PHA ; TO SQUARE TAY LDX #$1F CHECK CMP BOARD,X ; CHECK FOR BEQ TAKE ; CAPTURE DEX BPL CHECK TAKE LDA #$CC STA BOARD,X TXA ; CAPTURED PHA ; PIECE LDX PIECE LDA BOARD,X STY BOARD,X ; FROM PHA ; SQUARE TXA PHA ; PIECE LDA MOVEN PHA ; MOVEN STRV TSX STX SP2 ; SWITCH LDX SP1 ; STACKS TXS ; BACK RTS ; CONTINUATION OF SUB STRATGY ; -CHECKS FOR CHECK OR CHECKMATE ; AND ASSIGNS VALUE TO MOVE CKMATE LDY BMAXC ; CAN BLK CAP CPX POINTS ; MY KING? BNE NOCHEK LDA #$00 ; GULP! BEQ RETV ; DUMB MOVE! NOCHEK LDX BMOB ; IS BLACK BNE RETV ; UNABLE TO LDX WMAXP ; MOVE AND BNE RETV ; KING IN CH? LDA #$FF ; YES! MATE RETV LDX #$04 ; RESTORE STX STATE ; STATE=4 ; THE VALUE OF THE MOVE (IN ACCU) ; IS COMPARED TO THE BEST MOVE AND ; REPLACES IT IF IT IS BETTER PUSH CMP BESTV ; IS THIS BEST BCC RETP ; MOVE SO FAR? BEQ RETP STA BESTV ; YES! LDA PIECE ; SAVE IT STA BESTP LDA SQUARE STA BESTM ; FLASH DISPLAY RETP LDA prompt ; get prompt character EOR #$1F ; toggle between [SPACE] and '?' STA prompt ; save it back JMP UpdateDisp ; update prompt & display ; MAIN PROGRAM TO PLAY CHESS ; PLAY FROM OPENING OR THINK GO LDX OMOVE ; OPENING? BMI NOOPEN ; -NO *ADD CHANGE FROM BPL LDA DIS3 ; -YES WAS CMP OPNING,X ; OPPONENT'S BNE END ; MOVE OK? DEX LDA OPNING,X ; GET NEXT STA DIS1 ; CANNED DEX ; OPENING MOVE LDA OPNING,X STA DIS3 ; DISPLAY IT DEX STX OMOVE ; MOVE IT BNE MV2 ; (JMP) END LDA #$FF ; *ADD - STOP CANNED MOVES STA OMOVE ; FLAG OPENING NOOPEN LDX #$0C ; FINISHED STX STATE ; STATE=C STX BESTV ; CLEAR BESTV LDX #$14 ; GENERATE P JSR GNMX ; MOVES LDX #$04 ; STATE=4 STX STATE ; GENERATE AND JSR GNMZ ; TEST AVAILABLE ; ; MOVES LDX BESTV ; GET BEST MOVE CPX #$0F ; IF NONE BCC MATE ; OH OH! MV2 LDX BESTP ; MOVE LDA BOARD,X ; THE STA BESTV ; BEST STX PIECE ; MOVE LDA BESTM STA SQUARE ; AND DISPLAY JSR MOVE ; IT JSR DISP3 ; piece into display JMP CHESS MATE LDA #$FF ; RESIGN RTS ; OR STALEMATE ; SUBROUTINE TO ENTER THE ; PLAYER'S MOVE DISMV LDX #$04 ; ROTATE DROL ASL DIS3 ; KEY ROL DIS2 ; INTO DEX ; DISPLAY BNE DROL ; ORA DIS3 STA DIS3 STA SQUARE RTS ; THE FOLLOWING SUBROUTINE ASSIGNS ; A VALUE TO THE MOVE UNDER ; CONSIDERATION AND RETURNS IT IN ; THE ACCUMULATOR STRATGY CLC LDA #$80 ADC WMOB ; PARAMETERS ADC WMAXC ; WITH WHEIGHT ADC WCC ; OF O25 ADC WCAP1 ADC WCAP2 SEC SBC PMAXC SBC PCC SBC BCAP0 SBC BCAP1 SBC BCAP2 SBC PMOB SBC BMOB BCS POS ; UNDERFLOW LDA #$00 ; PREVENTION POS LSR CLC ; ************** ADC #$40 ADC WMAXC ; PARAMETERS ADC WCC ; WITH WEIGHT SEC ; OF 05 SBC BMAXC LSR ; ************** CLC ADC #$90 ADC WCAP0 ; PARAMETERS ADC WCAP0 ; WITH WEIGHT ADC WCAP0 ; OF 10 ADC WCAP0 ADC WCAP1 SEC ; [UNDER OR OVER- SBC BMAXC ; FLOW MAY OCCUR SBC BMAXC ; FROM THIS SBC _BCC ; SECTION] SBC _BCC SBC BCAP1 LDX SQUARE ; *************** CPX #$33 BEQ POSN ; POSITION CPX #$34 ; BONUS FOR BEQ POSN ; MOVE TO CPX #$22 ; CENTRE BEQ POSN ; OR CPX #$25 ; OUT OF BEQ POSN ; BACK RANK LDX PIECE BEQ NOPOSN LDY BOARD,X CPY #$10 BPL NOPOSN POSN CLC ADC #$02 NOPOSN JMP CKMATE ; CONTINUE ; most new code from here on ; update move display, do prompt, piece, 'FROM' and 'TO' squares UpdateDisp LDA #$26 ; set cursor X STA DispPosX ; set cursor X LDA #$08 ; set cursor Y STA DispPosY ; set cursor Y LDA prompt ; prompt JSR asciiout ; byte out to display JSR space ; [SPACE] out to display JSR DisPiece ; display piece (from byte in DIS1) JSR space ; [SPACE] out to display LDA DIS2 ; 2nd display byte JSR PSquare ; Print square JSR space ; [SPACE] out to display LDA DIS3 ; 3rd display byte JMP PSquare ; Print square ; draw board on an ASCII character display ; the display in the simulator has cursor ; positioning. Other displays may use escape ; codes to the same ends. DrawBoard JSR Print_c_ ; print copyright LDA #$00 ; set initial position (0,0) is top left STA DispPosX ; set cursor X STA DispPosY ; set cursor Y JSR PColNum ; print column labels JSR Hline ; print horizontal line LDY #$00 ; init board location PNewVert JSR PRowNum ; print row number PVert LDA #'|' ; print vertical edge JSR asciiout ; byte out to display LDX #$1F ; for each piece TYA ; copy square # PPiece CMP BOARD,X ; this piece in this square? BEQ PieceOut ; if so print the piece's color and type DEX ; else try next piece BPL PPiece ; if not done then loop TYA ; copy square # ASL ; shift column LSB into Cb ASL ; ASL ; ASL ; TYA ; copy square # again ADC #$00 ; add column LSB LSR ; result into carry LDA #' ' ; assume white square BCS Iswhite ; branch if white LDA #'#' ; else make square black Iswhite JSR asciiout ; byte out to display JSR asciiout ; byte out to display PNextCol INY ; next column TYA ; get square # AND #$08 ; have we completed the row? BEQ PVert ; if not go do next column LDA #'|' ; yes, put the right edge on JSR asciiout ; byte out to display JSR PRowNum ; print row number JSR CRLF ; print CRLF JSR Hline ; print horizontal line TYA ; copy square # CLC ; clear for add ADC #$08 ; increment to beginning of next row BMI PColNum ; done so go finish board TAY ; else copy new square # BPL PNewVert ; go do next row ; output piece's color & type PieceOut LDA #'W' ; assume white CPX #$10 ; compare with breakpoint (result in Cb) BIT reverse ; test reverse byte BEQ Noflip ; branch if not reverse ; else toggle Cb state ROL ; Cb into D0 EOR #$01 ; toggle bit ROR ; D0 into Cb Noflip BCC NotBlack ; branch if white LDA #'B' ; else make black NotBlack JSR asciiout ; byte out to display TXA ; copy piece AND #$0F ; mask black/white TAX ; back to index LDA P_piece,x ; get current piece 2nd byte JSR asciiout ; byte out to display BNE PNextCol ; branch always ; print " ", line of -'s then [CR][LF] Hline JSR space ; [SPACE] out to display JSR asciiout ; byte out to display (2nd [SPACE]) LDA #'-' ; line of -'s LDX #$19 ; 25 -'s to do HlineL JSR asciiout ; byte out to display DEX ; decrement count BNE HlineL ; loop if not all done ; do newline CRLF LDA #$0D ; [CR] JSR asciiout ; byte out to display LDA #$0A ; [LF] JMP asciiout ; byte out to display & return ; print the column labels PColNum JSR space ; [SPACE] out to display JSR asciiout ; byte out to display (2nd [SPACE]) LDX #$00 ; clear index PNextCNum JSR space ; [SPACE] out to display TXA ; get column number JSR hexout ; A out as hex INX ; next column CPX #$08 ; is it done? BNE PNextCNum ; loop if not BEQ CRLF ; else do newline and return ; print (c) message ; text lines are ... ; Xpos,Ypos,"text",0 ; .. for lines with following lines and ... ; Xpos,Ypos,"text",255 ; for the last line Print_c_ LDX #$FF ; initial -1 Print_c_n INX ; increment index LDA _c_,X ; get cursor X STA DispPosX ; set cursor X INX ; increment index LDA _c_,X ; get cursor Y STA DispPosY ; set cursor Y INX ; increment index Print_c_l LDA _c_,X ; get byte BEQ Print_c_n ; do next line if $00 [EOL] BMI Print_c_e ; exit if $FF [EOT] JSR asciiout ; byte out to display INX ; increment index BNE Print_c_l ; loop Print_c_e RTS ; wait for key asciiin LDA ACIAsimrd ; get chr BEQ asciiin ; no char to get CMP #'a' ; lowe case ASCII BCC asciirts ; skip if not >= AND #$DF ; # and upper case alpha only asciirts RTS PRowNum TYA ; copy row number PSquare AND #$77 ; mask unused bits ; output A as two hex digits hexout PHA ; save for lower digit LSR ; shift upper .. LSR ; .. nibble to .. LSR ; .. lower nibble .. LSR ; .. and clear upper JSR PrintDig ; output hex digit PLA ; get byte back AND #$0F ; clear upper nibble PrintDig SED ; set for hex convert CMP #$0A ; compare with breakpoint ADC #'0' ; add to "0" CLD ; clear again ; byte out to display asciiout STA ACIAsimwr ; byte out to port RTS space LDA #$20 ; [SPACE] BNE asciiout ; print and return ; display piece byte in DIS1 as ASCII string DisPiece LDA DIS1 ; get piece for this move BMI DisSpecial ; branch if not piece AND #$0F ; don't care black or white ASL ; *2 ASL ; *4 ASL ; *8 TAX ; copy index DisString LDY #$08 ; character count DisLoop LDA PieceName,X ; get byte JSR asciiout ; out to display INX ; increment index DEY ; decrement count BNE DisLoop ; loop if not done RTS ; set X for 'special' $CC, $EE and $FF piece codes, else set null DisSpecial CMP #$CC ; compare with reset BNE NotReset ; branch if not reset LDX #PRes-PieceName ; set pointer BNE DisString ; go print it NotReset CMP #$EE ; compare with exchange BNE NotExcg ; branch if not exchange LDX #PExg-PieceName ; set pointer BNE DisString ; go print it NotExcg ; else null CMP #$FF ; compare with check mate BNE NotChkm ; branch if not check mate LDX #PCkm-PieceName ; set pointer BNE DisString ; go print it NotChkm ; else null LDX #PNul-PieceName ; set pointer BNE DisString ; go print it ; text descriptions for the byte in DIS1 PieceName .byte "King " .byte "Queen " .byte "K Rook " .byte "Q Rook " .byte "K Bishop" .byte "Q Bishop" .byte "K Knight" .byte "Q Knight" .byte "K R Pawn" .byte "Q R Pawn" .byte "K N Pawn" .byte "Q N Pawn" .byte "K B Pawn" .byte "Q B Pawn" .byte "Q Pawn " .byte "K Pawn " PRes .byte "Reset " PExg .byte "Exchange" PCkm .byte "Mate" PNul .byte " " ; copyright banner _c_ .byte $24,$01,"+--------------------+",$00 .byte $24,$02,"| MicroChess |",$00 .byte $24,$03,"| (c) 1976-2002 |",$00 .byte $24,$04,"| Peter Jennings |",$00 .byte $24,$05,"| |",$00 .byte $24,$06,"+--------------------+",$FF ; piece character table P_piece .byte "KQCCBBkkPPPPPPPP" ; end of new code ; BLOCK DATA ; *= $1580 ; initial positions SETW .byte $03, $04, $00, $07, $02, $05, $01, $06 .byte $10, $17, $11, $16, $12, $15, $14, $13 .byte $73, $74, $70, $77, $72, $75, $71, $76 .byte $60, $67, $61, $66, $62, $65, $64, $63 MOVEX .byte $00, $F0, $FF, $01, $10, $11, $0F, $EF, $F1 .byte $DF, $E1, $EE, $F2, $12, $0E, $1F, $21 POINTS .byte $0B, $0A, $06, $06, $04, $04, $04, $04 .byte $02, $02, $02, $02, $02, $02, $02, $02 OPNING .byte $99, $25, $0B, $25, $01, $00, $33, $25 .byte $07, $36, $34, $0D, $34, $34, $0E, $52 .byte $25, $0D, $45, $35, $04, $55, $22, $06 .byte $43, $33, $0F, $CC This version is posted with the kind permission of Peter Jennings