aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f9034
1 files changed, 24 insertions, 10 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index 9817775..f66250c 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -89,7 +89,7 @@ contains
function generate_one_instuction_html(req) result(res)
use captain_db
use server_response
- use request_utils, only: get_status_utf8, render_jobs_links, generate_simple_pager
+ use request_utils, only: get_player_status_utf8, render_jobs_links, generate_simple_pager
implicit none
type(request)::req
@@ -170,12 +170,7 @@ contains
do i = 1, n_players
call get_player_name(players(i), player_name)
- if(is_player_busy(players(i))) then
- player_status = get_status_utf8(PLAYER_STATUS_BUSY)
- else
- player_status = get_status_utf8(PLAYER_STATUS_IDLE)
- end if
-
+ player_status = get_player_status_utf8(players(i))
one_link => html_link(req%page//"?launch="//trim(player_name), &
trim(player_status)//" "//trim(player_name))
@@ -511,12 +506,14 @@ contains
function generate_players_html() result(res)
use captain_db
+ use request_utils, only: get_status_utf8
implicit none
character(len=:), pointer::res
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::players
- integer::n, i, nsize
+ integer::n, i, nsize, pid
+ character(4)::player_status
character(len=:), pointer::one_player
n = get_player_count()
@@ -539,8 +536,20 @@ contains
res = "<h2>Existing Players</h2>"//new_line(' ')//"<ul>"
do i = 1, n
+
+ pid = get_player_id(players(i))
+ if(is_player_online(pid)) then
+ if(is_player_busy(pid)) then
+ player_status = get_status_utf8(PLAYER_STATUS_BUSY)
+ else
+ player_status = get_status_utf8(PLAYER_STATUS_IDLE)
+ end if
+ else
+ player_status = get_status_utf8(PLAYER_STATUS_OFFLINE)
+ end if
+
one_player => html_link("players/"//trim(players(i))//".html", &
- trim(players(i)))
+ trim(player_status)//" "//trim(players(i)))
res = trim(res)//new_line(' ')//"<li>"//trim(one_player)//"</li>"
deallocate(one_player)
end do
@@ -580,7 +589,12 @@ contains
n = get_instructions_count(player=pid)
allocate(character(len=(2*n*PLAYER_NAME_LENGTH + 1024)) :: res)
- res = "<h2>"//trim(player_name)//"</h2>"
+ res = "<h2>"//trim(player_name)
+ if(is_player_online(pid)) then
+ res = trim(res)//" - Online</h2>"
+ else
+ res = trim(res)//" - Offline</h2>"
+ end if
! Last checkin
call get_last_checkin_time(pid, values)