aboutsummaryrefslogtreecommitdiff
path: root/captain/requtils.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 12:36:04 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 12:36:04 -0400
commita67622fdc0dbe7f6be04667663f58b31fbf30a8d (patch)
tree872eaea37f8711058cfab97232d9abcea2b86133 /captain/requtils.f90
parent4e7de7784173cc8b9539fdda33861dec87ab0a74 (diff)
downloadlevitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.tar.gz
levitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.zip
Job listing now works through CGI
Diffstat (limited to 'captain/requtils.f90')
-rw-r--r--captain/requtils.f90130
1 files changed, 130 insertions, 0 deletions
diff --git a/captain/requtils.f90 b/captain/requtils.f90
index 04ef6cf..742f8ac 100644
--- a/captain/requtils.f90
+++ b/captain/requtils.f90
@@ -84,6 +84,39 @@ contains
end subroutine basic_mimetype
+ pure function get_status_utf8(status) result(res)
+ use captain_db
+ implicit none
+
+ integer, intent(in)::status
+ character(4)::res
+
+ select case(status)
+
+ case(JOB_STATUS_SUCCESS)
+ ! Check mark 0x2714
+ res = char(226)//char(156)//char(148)//" "
+
+ case(JOB_STATUS_FAILURE)
+ ! Ballot x 0x2717
+ res = char(226)//char(156)//char(151)//" "
+
+ case(JOB_STATUS_WORKING)
+ ! Runner 0x1f3c3
+ res = char(240)//char(159)//char(143)//char(131)
+
+ case(PLAYER_STATUS_IDLE)
+ ! Sleeping 0x1f4a4
+ res = char(240)//char(159)//char(146)//char(164)
+
+ case(JOB_STATUS_PENDING)
+ ! Envelope 0x2709
+ res = char(226)//char(156)//char(137)//" "
+
+ end select
+
+ end function get_status_utf8
+
function is_request_static(req)
use server_response
use logging
@@ -152,5 +185,102 @@ contains
end if
end function request_static
+
+ function render_jobs_links(jobs, startindex, stopindex, gemini_mode) result(res)
+ use captain_db
+ implicit none
+
+ type(job), dimension(:), pointer, intent(in)::jobs
+ integer, intent(in), optional::startindex, stopindex
+ logical, intent(in)::gemini_mode
+ character(len=:), pointer::res
+
+ integer::nsize, i, first, last
+ character(len=16)::int_text
+ character(len=(2*PLAYER_NAME_LENGTH + 64))::link
+ character(PLAYER_NAME_LENGTH)::player, instruction
+ character(1)::nl = new_line(' ')
+
+ if(.not. associated(jobs)) then
+ allocate(character(len=32)::res)
+ res = "None Yet"
+
+ else
+ first = 1
+ if(present(startindex)) then
+ first = startindex
+ end if
+
+ last = size(jobs)
+ if(present(stopindex)) then
+ last = min(size(jobs), stopindex)
+ end if
+
+ if(first <= last .and. first <= size(jobs)) then
+ nsize = (last-first+1)*(2*PLAYER_NAME_LENGTH + 64) + 32
+ allocate(character(len=nsize) :: res)
+
+ if(gemini_mode) then
+ res = " "
+ else
+ res ="<ul>"
+ end if
+
+ do i = first, last
+ call get_instruction_name(jobs(i)%instruction, instruction)
+ call get_player_name(jobs(i)%player, player)
+
+ write(int_text, '(I8)') jobs(i)%id
+
+ if(gemini_mode) then
+ link = "=> jobs/"//trim(adjustl(int_text))//".gmi "// &
+ trim(get_status_utf8(jobs(i)%status))//" Job "// &
+ trim(adjustl(int_text))//" - "//trim(instruction)
+
+ res = trim(res)//nl//nl//trim(link)
+ else
+ res = trim(res)//nl//' <li><div class="job_result_listitem">'
+
+ link = ' <p><strong><a href="jobs/'//trim(adjustl(int_text))//'.html" >'// &
+ trim(get_status_utf8(jobs(i)%status))//" Job "// &
+ trim(adjustl(int_text))//" - "//trim(instruction)// &
+ '</a></strong></p>'
+
+ res = trim(res)//nl//trim(link)//nl//" <p><em>"
+ endif
+
+ select case(jobs(i)%status)
+ case(JOB_STATUS_SUCCESS, JOB_STATUS_FAILURE)
+ res = trim(res)//nl//"Completed on"
+ case(JOB_STATUS_PENDING)
+ res = trim(res)//nl//"Waiting to run on"
+ case(JOB_STATUS_WORKING)
+ res = trim(res)//nl//"Running on"
+ end select
+
+ res = trim(res)//" "//trim(player)// &
+ " - Last Update: "//trim(jobs(i)%time)
+
+ if(.not. gemini_mode) then
+ res = trim(res)//"</em></p>"//nl//" </div></li>"
+ end if
+
+ end do
+
+ if(.not. gemini_mode) then
+ res = trim(res)//nl//"</ul>"
+ end if
+
+ else
+
+ ! Indices exceed array
+ allocate(character(len=64)::res)
+ write(int_text, '(I8)') first
+ res = "None at index "//trim(adjustl(int_text))//" or beyond"
+
+ end if
+ end if
+
+ end function render_jobs_links
end module request_utils \ No newline at end of file