TicTacToe function
1. The method
!Tic tac toe program
!
!This program reads two idexes i and j of an element of a matrix 3x3 (board(3,3))
!and assign for the related element the character "X" or "O".
!
!The program calls first the subroutine initialize(board) to initialize the elements
!of the matrix by dots. Then reads indexes (1 2 or3 only) from the file "moves.txt ".
!To assigne "X" or "O" to the element of a matrix, a counter is incremented to fix
!the first turn for "X" by using the LOGICAL function player(counter).
!If the three elements of a line or of a column or
!of the two diagonals are equal, then the element "X" or "O" WINS.
!
!Finally, the results are written in the output file results.txt. via the
!subroutine resultboard(board)
!
! --------------------------------------------------
2. Example in Fortran 90 language:
!1. Main program:
!-----------------
PROGRAM tictactoe
IMPLICIT NONE
INTEGER:: x, y, iostatus,counter
Character:: board(3,3)
logicaL:: player
! Opening the file: moves.txt
OPEN(UNIT=16,FILE="moves.txt")
counter=1
! Initialize the matrix
CAll initialize(board)
DO
! reading indexes from the file: moves.txt
READ(16,*,iostat=iostatus) x,y
!Exit at the end
IF(iostatus /=0) EXIT
!Just three integers
IF ((x<1) .OR. (x>3) .OR. (y<1) .OR. (y>3)) THEN
write(*,*) "The board contains 3 rows and 3 columns only, please check your file input"
stop
ELSE
if (board(x,y) == ".") THEN
! In the case of the LOGICAL function player returns TRUE
IF(player(counter)) THEn
board(x,y) = "X"
ELSE
board(x,y) = "O"
END IF
ELSE
write(*,*) "The position"," (",x,",",y,") ","is occupied"
stop
END IF
END IF
!Infrement the counter
counter = counter + 1
!If the three elements of a line or of a column or
!of the two diagonals are equal, then the element "X" or "O" WINS.
IF (board(1,1)==board(1,2) .AND. board(1,2)==board(1,3) .AND. board(1,1) /= "."
.AND. board(1,2) /= "." .AND. board(1,3) /= ".") THEN
write(*,*) board(1,1), " wins"
call resultboard(board)
stop
elseif(board(2,1)==board(2,2) .AND. board(2,2)==board(2,3) .AND. board(2,1) /= "."
.AND. board(2,2) /= "." .AND. board(2,3) /= ".") THEN
write(*,*) board(2,1), " wins"
call resultboard(board)
stop
elseif(board(3,1)==board(3,2) .AND. board(3,2)==board(3,3) .AND. board(3,1) /= "."
.AND. board(3,2) /= "." .AND. board(3,3) /= ".") THEN
write(*,*) board(3,1), " wins"
call resultboard(board)
stop
elseif(board(1,1)==board(2,1) .AND. board(2,1)==board(3,1) .AND. board(1,1) /= "."
.AND. board(2,1) /= "." .AND. board(3,1) /= ".") THEN
write(*,*) board(1,1), " wins"
call resultboard(board)
stop
elseif(board(1,2)==board(2,2) .AND. board(2,2)==board(3,2) .AND. board(1,2) /= "."
.AND. board(2,2) /= "." .AND. board(3,2) /= ".") THEN
write(*,*) board(1,2), " wins"
call resultboard(board)
stop
elseif(board(1,3)==board(2,3) .AND. board(2,3)==board(3,3) .AND. board(1,3) /= "."
.AND. board(2,3) /= "." .AND. board(3,3) /= ".") THEN
write(*,*) board(1,3), " wins"
call resultboard(board)
stop
elseif(board(1,1)==board(2,2) .AND. board(2,2)==board(3,3) .AND. board(1,1) /= "."
.AND. board(2,2) /= "." .AND. board(3,3) /= ".") THEN
write(*,*) board(1,1), " wins"
call resultboard(board)
stop
elseif(board(3,1)==board(2,2) .AND. board(2,2)==board(1,3) .AND. board(3,1) /= "."
.AND. board(2,2) /= "." .AND. board(1,3) /= ".") THEN
write(*,*) board(3,1), " wins"
call resultboard(board)
stop
end if
END DO
!If just an element of the matrix is steel a dot, the game is still not completed
IF(board(1,1)=="." .OR. board(1,2)=="." .OR. board(1,3)=="." .OR. board(2,1)=="."
.OR. board(2,2)=="." .OR. board(2,3)=="." .OR. board(3,1)=="." .OR. board(3,2)=="."
.OR. board(3,3)==".") then
write(*,*) "Incomplete Game"
call resultboard(board)
else
write(*,*) "Draw"
! Put the results in the file ""results.txt
call resultboard(board)
end if
CLOSE(16)
END PROGRAM tictactoe
!2. The subroutine to initialize the matrix borard(3,3)
!-------------------------------------------------------
subroutine initialize(a)
IMPLICIT NONE
INTEGER:: i, j
Character:: a(3,3)
Do i=1,3
DO j=1,3
a(i,j) = "."
END DO
END DO
END subroutine initialize
!3. The logical function allowing "X" to take the first , third, fifth ... turns
!--------------------------------------------------------------------------------
LOGICAL function player(counter)
IMPLICIT NONE
integer:: counter
IF(mod(counter,2) /= 0) THEN
player = .TRUE.
ELSE
player = .FALSE.
END IF
end function player
!4. The subroutine to output the results within the file results.txt
!--------------------------------------------------------------------
subroutine resultboard(b)
implicit none
integer:: i
character:: b(3,3)
OPEN(UNIT=15,FILE="results.txt")
do i=1,3
write(15,*) b(i,1), "|", b(i,2), "|", b(i,3)
end do
CLOSE(15)
end subroutine
! -------------------------------------------------- END
!Example:
!
!file moves.txt
!1 1
!1 2
!2 1
!2 3
!3 1
!3 2
!3 3
!
!file results.txt
! X|O|.
! X|.|O
! X|.|.
!The compiler SciTE.exe gives:
!>g77 -x f77 -ffree-form -W -Wall "ttt.f90" -o "ttt.exe"
!>Exit code: 0
!Running the program:
!C:\Fortran90>tictactoe
!X wins