87 lines
2.7 KiB
Fortran
87 lines
2.7 KiB
Fortran
program main
|
|
use iso_fortran_env
|
|
use iso_c_binding
|
|
use raylib
|
|
use player_mod
|
|
use json_module
|
|
implicit none
|
|
|
|
integer(c_int) :: screen_width = 800
|
|
integer(c_int) :: screen_height = 450
|
|
|
|
type(camera3d), target :: camera
|
|
type(player) :: me
|
|
type(player), dimension(:), allocatable :: players
|
|
character(len=24) :: username
|
|
character(len=24) :: password
|
|
integer :: i, status
|
|
logical :: player_updated, exist
|
|
real(c_double) :: time
|
|
|
|
call getarg(1, username)
|
|
call getarg(2, password)
|
|
|
|
me = player(username, vector3(0.0_c_float, 1.0_c_float, 2.0_c_float), PURPLE)
|
|
players = me%login(password)
|
|
|
|
camera%position = vector3(me%position%x,me%position%y + 10.0_c_float ,me%position%z + 10.0_c_float) !Camera position
|
|
camera%target = vector3(me%position%x,me%position%y,me%position%z) !Camera looking at point
|
|
camera%up = vector3(0.0_c_float, 1.0_c_float, 0.0_c_float) !Camera up vector(rotation towards target)
|
|
camera%fovy = 45.0_c_float !Camera field - of - view Y
|
|
camera%projection = CAMERA_PERSPECTIVE !Camera projection type
|
|
|
|
call init_window(screen_width, screen_height, "fortran client : raylib"//c_null_char)
|
|
call set_target_fps(60_c_int)
|
|
|
|
!Main game loop
|
|
do while (.not. window_should_close()) ! Detect window close button or ESC key
|
|
|
|
if (is_key_down(KEY_RIGHT)) then
|
|
me%position%x = me%position%x + 0.2_c_float
|
|
player_updated = .true.
|
|
else if (is_key_down(KEY_LEFT)) then
|
|
me%position%x = me%position%x - 0.2_c_float
|
|
player_updated = .true.
|
|
else if (is_key_down(KEY_DOWN)) then
|
|
me%position%z = me%position%z + 0.2_c_float
|
|
player_updated = .true.
|
|
else if (is_key_down(KEY_UP)) then
|
|
me%position%z = me%position%z - 0.2_c_float
|
|
player_updated = .true.
|
|
end if
|
|
|
|
call me%sync_camera(camera)
|
|
|
|
time = get_time()
|
|
if (modulo(time, 1.0) .ge. 0.58_c_double) then
|
|
if (player_updated) then
|
|
players = me%move()
|
|
else
|
|
players = me%ping()
|
|
end if
|
|
end if
|
|
|
|
call begin_drawing()
|
|
call clear_background(RAYWHITE)
|
|
|
|
call begin_mode_3d(camera)
|
|
! Draw floor
|
|
call draw_grid(30_c_int, 1.0_c_float)
|
|
|
|
call draw_cube(me%position, 0.5_c_float, 0.5_c_float, 0.5_c_float, me%apperance)
|
|
do i = 1, size(players)
|
|
call draw_cube(players(i)%position, 0.5_c_float, 0.5_c_float, 0.5_c_float, players(i)%apperance)
|
|
end do
|
|
call end_mode_3d()
|
|
call end_drawing()
|
|
|
|
end do
|
|
|
|
players = me%logout()
|
|
if (allocated(players)) then
|
|
deallocate (players)
|
|
end if
|
|
call close_window() !Close window and OpenGL context
|
|
|
|
end program main
|