aboutsummaryrefslogtreecommitdiff
path: root/captain/web.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/web.f90
parent4e7de7784173cc8b9539fdda33861dec87ab0a74 (diff)
downloadlevitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.tar.gz
levitating-a67622fdc0dbe7f6be04667663f58b31fbf30a8d.zip
Job listing now works through CGI
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f9069
1 files changed, 67 insertions, 2 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index e466c63..e232e2d 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -159,7 +159,72 @@ contains
end if
+ res = trim(res)//nl//"</ul>"
+
end function generate_releases_html
+
+ function generate_jobs_html(req) result(res)
+ use captain_db
+ use server_response
+ use request_utils, only: render_jobs_links
+ use logging
+ implicit none
+
+ type(request)::req
+ character(len=:), pointer::res
+ type(job), dimension(:), pointer::jobs
+ integer::n, nsize
+ integer::i_start_jobs, ierr
+
+ character(len=:), pointer::linklist
+ character(10)::pager
+
+ n = get_jobs_count()
+ if(n == 0) then
+
+ allocate(character(len=1024) :: res)
+
+ res = "None Yet"
+
+ else
+ if(associated(req%query_string)) then
+ read(req%query_string, *, iostat=ierr) i_start_jobs
+ else
+ ierr = -1
+ end if
+
+ if(ierr /= 0) then
+ i_start_jobs = 1
+ end if
+
+ jobs => get_jobs()
+
+ ! 15 per page
+ nsize = 15*(2*PLAYER_NAME_LENGTH + 64) + 1024
+ allocate(character(len=nsize) :: res)
+
+ res = " "
+
+ linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n), .false.)
+ res = trim(res)//new_line(' ')//trim(linklist)
+
+ ! Pagers
+ res = trim(res)//new_line(' ')//"<p>"
+ if(i_start_jobs /= 1) then
+ write(pager, '(I8)') max(i_start_jobs - 15, 1)
+ res = trim(res)//'<a href="jobs.html?'//trim(adjustl(pager))//'">&lt;&lt; Newer</a> |'
+ end if
+ if(i_start_jobs+14 < n) then
+ write(pager, '(I8)') i_start_jobs + 15
+ res = trim(res)//' <a href="jobs.html?'//trim(adjustl(pager))//'">Older &gt;&gt;</a>'
+ end if
+ res = trim(res)//"</p>"
+
+ deallocate(linklist)
+
+ end if
+
+ end function generate_jobs_html
function request_templated(req) result(resp)
use page_template
@@ -199,8 +264,8 @@ contains
else if(trim(req%location) == "/jobs.html") then
call page%assign('title', 'Jobs')
- !contents => generate_jobs_gemini(req)
- !call page%assign('contents', contents)
+ contents => generate_jobs_html(req)
+ call page%assign('contents', contents)
else if(trim(req%location) == "/players.html") then