aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 16:00:59 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 16:00:59 -0400
commit55870299e41492ee8ab6c50116061f48f06fcd7d (patch)
tree046ea3e9d4dffe186dff78c3b5fb7d87aca9d08c /captain/web.f90
parenta67622fdc0dbe7f6be04667663f58b31fbf30a8d (diff)
downloadlevitating-55870299e41492ee8ab6c50116061f48f06fcd7d.tar.gz
levitating-55870299e41492ee8ab6c50116061f48f06fcd7d.zip
Individual job results can now be displayed via CGI
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f9092
1 files changed, 88 insertions, 4 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index e232e2d..3ac260a 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -64,6 +64,88 @@ contains
end function html_link
+ function generate_one_job_html(req) result(res)
+ 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
+ character(len=:), pointer::res
+
+ character(4)::status
+ integer::i, j, job_id
+ type(job)::one_job
+
+ character(PLAYER_NAME_LENGTH)::player
+ character(1)::nl = new_line(' ')
+
+ type(task), dimension(:), pointer::tasks
+ character(32)::task_text, job_text
+ character(len=:), pointer::task_results_filename, one_link
+
+ logical::file_exists
+
+ res => null()
+
+ ! Ugh, all this nonsense
+ call req%last_component(job_text)
+ j = index(job_text, ".", back=.true.)
+ job_text(j:len(job_text)) = " "
+ read(job_text, '(I8)') job_id
+ one_job = get_job(job_id)
+
+ if(one_job%id >= 0) then
+ allocate(character(len=1024) :: res)
+
+ status = get_status_utf8(one_job%status)
+ res = "<h2>Status - "//status//"</h2>"
+
+ call get_player_name(one_job%player, player)
+ res = trim(res)//nl//nl//"<p><em>Running on "//trim(player)//nl// &
+ "Last update at: "//one_job%time//"</em></p>"
+
+ res = trim(res)//nl//nl//"<h3>Task Results</h3>"
+
+ tasks => get_job_tasks(job_id)
+ if(associated(tasks)) then
+ res = trim(res)//nl//"<ul>"
+ do i = 1, size(tasks)
+ status = get_status_utf8(tasks(i)%status)
+ task_results_filename => get_task_result_static_filename(one_job%id, i, no_path=.true.)
+
+ inquire(file=task_results_filename, exist=file_exists)
+
+ write(task_text, '(I8)') i
+
+ if(file_exists) then
+ one_link => html_link("../results/"//task_results_filename, &
+ trim(status)//" - Task "//trim(adjustl(task_text)))
+
+ res = trim(res)//nl//" <li>"//trim(one_link)//"</li>"
+ deallocate(one_link)
+ else
+ res = trim(res)//nl//" <li>"//trim(status)//" - Task "//trim(adjustl(task_text))//"</li>"
+ end if
+
+ deallocate(task_results_filename)
+ end do
+ res = trim(res)//nl//"</ul>"
+ deallocate(tasks)
+ else
+ res = trim(res)//nl//nl//"<p><strong>None reported yet</strong></p>"
+ end if
+
+ else
+
+ allocate(character(len=64) :: res)
+ write(res, '(A20, 1X, I5)') "No record of:", job_id
+
+ end if
+
+ end function generate_one_job_html
+
function generate_releases_html(req) result(res)
use utilities
use server_response
@@ -232,6 +314,7 @@ contains
use logging
use server_response, only:request, response
use http, only: HTTP_CODE_SUCCESS, HTTP_CODE_NOTFOUND
+ use request_utils, only: get_job_page_title
implicit none
type(request), intent(in)::req
@@ -242,6 +325,7 @@ contains
character(64)::first
character(len=:), pointer::contents
+ character(128)::job_page_title
call template_filepath("index.html", template_file)
call page%init(trim(template_file))
@@ -293,10 +377,10 @@ contains
else if(trim(first) == "jobs") then
- !call get_job_page_title(req, job_page_title)
- !call page%assign('title', trim(job_page_title))
- !contents => generate_one_job_gemini(req)
- !call page%assign('contents', contents)
+ call get_job_page_title(req, job_page_title)
+ call page%assign('title', trim(job_page_title))
+ contents => generate_one_job_html(req)
+ call page%assign('contents', contents)
else