mmo-project/fortran/server/app/main.f90

57 lines
1.6 KiB
Fortran
Raw Normal View History

program main
use iso_fortran_env
2023-09-10 20:22:32 -04:00
use, intrinsic :: iso_c_binding
use db
implicit none
2023-09-10 20:22:32 -04:00
type(db_type) :: db
character(len=128):: db_path
2023-09-10 20:22:32 -04:00
character(len=24):: username
real(kind=c_double) :: x_pos
real(kind=c_double) :: y_pos
integer :: command, rc
logical :: exist
inquire (file="debug.log", exist=exist)
if (exist) then
open (12, file="debug.log", status="old", position="append", action="write")
else
open (12, file="debug.log", status="new", action="write")
end if
2023-09-10 20:22:32 -04:00
call getarg(1, db_path)
2023-09-10 20:22:32 -04:00
inquire (file=db_path(:Len_Trim(db_path)), exist=exist)
if (.not. exist) then
stop 1
end if
2023-09-10 20:22:32 -04:00
rc = db_open(db, db_path(:Len_Trim(db_path)))
! do while not logged out
server_loop: do
2023-09-10 20:22:32 -04:00
! read message from stdin
read(input_unit, "(i3, 1x, a24, 1x, f8.2, 1x, f8.2)") command, username, x_pos, y_pos
if (command .eq. 0) then ! get all logged in users and return their positions to client
rc = db_count_logged_in_users(db)
rc = db_get_logged_in_users(db)
else if (command .eq. 1) then
rc = db_login_user(db, username)
rc = db_count_logged_in_users(db)
rc = db_get_logged_in_users(db)
else if (command .eq. 3) then ! update new pos to database
rc = db_move_user(db, username, x_pos, y_pos)
rc = db_count_logged_in_users(db)
rc = db_get_logged_in_users(db)
else ! (2) if logout update logged_in to database
rc = db_logout_user(db, username)
exit server_loop
end if
end do server_loop
rc = db_close(db)
close(12)
end program main