aboutsummaryrefslogtreecommitdiff
path: root/captain/external.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/external.f90
parent4e7de7784173cc8b9539fdda33861dec87ab0a74 (diff)
downloadlevitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.tar.gz
levitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.zip
Job listing now works through CGI
Diffstat (limited to 'captain/external.f90')
-rw-r--r--captain/external.f90111
1 files changed, 6 insertions, 105 deletions
diff --git a/captain/external.f90 b/captain/external.f90
index 7b1826a..49331ba 100644
--- a/captain/external.f90
+++ b/captain/external.f90
@@ -25,112 +25,10 @@ implicit none
contains
- 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 render_jobs_links(jobs, startindex, stopindex) result(res)
- use captain_db
- implicit none
-
- type(job), dimension(:), pointer, intent(in)::jobs
- integer, intent(in), optional::startindex, stopindex
- 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)
- allocate(character(len=nsize) :: res)
- res = " "
-
- 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
- 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//link
-
- 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)
- end do
-
- 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
-
function generate_jobs_gemini(req) result(res)
use captain_db
use server_response
+ use request_utils, only: render_jobs_links
use logging
implicit none
@@ -168,7 +66,7 @@ contains
res = "## Jobs "
- linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n))
+ linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n), .true.)
res = trim(res)//trim(linklist)
call write_log(linklist)
deallocate(linklist)
@@ -181,6 +79,7 @@ contains
use captain_db
use server_response
use special_filenames, only: get_task_result_static_filename
+ use request_utils, only: get_status_utf8
implicit none
type(request), intent(in)::req
@@ -405,6 +304,8 @@ contains
function generate_one_instuction_gemini(req) result(res)
use captain_db
use server_response
+ use request_utils, only: get_status_utf8
+ use request_utils, only: render_jobs_links
implicit none
type(request)::req
@@ -430,7 +331,7 @@ contains
jobs => get_jobs_for_instruction(id_from_req)
if(associated(jobs)) then
n_jobs = size(jobs)
- job_link_text => render_jobs_links(jobs)
+ job_link_text => render_jobs_links(jobs, gemini_mode=.true.)
else
n_jobs = 0
job_link_text => null()