aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-06-21 11:04:31 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-06-21 11:04:31 -0400
commit20091904b7bf4b2074b45e25c7eee0e56d19348b (patch)
tree5c31004eff65466c84ed88cde77cbc712ba04ea6 /captain/web.f90
parentcd9283417a4b70335edf7ce0c5d15bfca111b807 (diff)
downloadlevitating-20091904b7bf4b2074b45e25c7eee0e56d19348b.tar.gz
levitating-20091904b7bf4b2074b45e25c7eee0e56d19348b.zip
Groups of instructions are now supported, allowing launching multiple jobs at once
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f90251
1 files changed, 248 insertions, 3 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index ccd3df0..9254658 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -253,7 +253,7 @@ contains
character(len=:), pointer::one_player, scanlink
- n = get_instuctions_count()
+ n = get_instructions_count()
if(n == 0) then
@@ -291,6 +291,227 @@ contains
deallocate(scanlink)
end function generate_instructions_html
+
+ function generate_groups_html(req) result(res)
+ use captain_db
+ use server_response, only:request
+ implicit none
+
+ type(request)::req
+ character(len=:), pointer::res
+ integer, dimension(:), pointer::groups
+ character(128)::one_group
+ integer::n, i
+
+ character(len=:), pointer::one_link
+
+ n = get_group_count_db()
+
+ if(n == 0) then
+
+ allocate(character(len=1024) :: res)
+ res = "None Yet"
+
+ else
+
+ allocate(character(len=(n*(256+64) + 384)) :: res)
+
+ res = "<h2>Groups</h2>"//new_line(' ')//"<ul>"
+
+ groups => get_groups_db()
+ do i=1, n
+ call get_group_name_db(groups(i), one_group)
+ one_link => html_link("groups/"//trim(one_group)//".html", &
+ trim(one_group))
+
+ res = trim(res)//new_line(' ')//"<li>"//trim(one_link)//"</li>"
+ deallocate(one_link)
+ end do
+
+ res = trim(res)//new_line(' ')//"</ul>"
+ deallocate(groups)
+
+ end if
+
+ res = trim(res)//new_line(' ')//"<h2>Management</h2>"
+
+ res = trim(res)//new_line(' ')// &
+ '<form action="groups/add.html" method="POST"><label for="name">Name:</label>'// &
+ '<input name="name" id="name" /><input type="submit" value="Add"/></form>'
+
+ end function generate_groups_html
+
+ function generate_one_group_html(req) result(res)
+ use captain_db
+ use server_response, only:request
+ use request_utils
+ use query_utilities
+ use logging
+ use remote_launch, only: launch_group
+ implicit none
+
+ type(request)::req
+ character(len=:), pointer::res
+
+ type(query)::q
+
+ character(128)::group_name, instruction_name, player_name
+ integer::id
+
+ type(group_entry), dimension(:), pointer::entries
+ type(work_pair), dimension(:), pointer::all_entries
+ character(len=:), pointer::one_link, delete_link, play_link, qreq
+
+ character(128)::launch_msg
+
+ integer::i, j, n_instructions_group, n_instructions_total
+
+ call req%path_component(2, group_name)
+ i = index(group_name, ".html")
+ group_name(i:128) = ' '
+
+ id = get_group_id_db(trim(group_name))
+ entries => null()
+ all_entries => null()
+
+ launch_msg = " "
+
+ if(associated(req%query_string)) then
+
+ call q%init(req%query_string)
+ qreq => q%get_value("add")
+
+ if(associated(qreq)) then
+
+ call write_log("ADD: "//trim(qreq))
+
+ i = index(qreq, ',')
+ player_name = qreq(i+1:len_trim(qreq))
+ instruction_name = qreq(1:i-1)
+
+ i = get_instruction_id(trim(instruction_name))
+ j = get_player_id(trim(player_name))
+
+ call add_entry_to_group_db(id, i, j)
+
+ deallocate(qreq)
+
+ else
+
+ qreq => q%get_value("delete")
+
+ if(associated(qreq)) then
+
+ i = index(qreq, ',')
+ player_name = qreq(i+1:len(qreq))
+ instruction_name = qreq(1:i-1)
+
+ i = get_instruction_id(trim(instruction_name))
+ j = get_player_id(trim(player_name))
+
+ call remove_entry_from_group_db(id, i, j)
+
+ deallocate(qreq)
+
+ else if(trim(req%query_string) == "launch") then
+
+ call launch_group(id)
+ write(launch_msg, '(I4, 1X, A13)') get_group_entries_count_db(id), "jobs launched"
+
+ else if(trim(req%query_string) == "destroy") then
+
+ call delete_group_db(id)
+
+ end if
+
+ end if
+
+ call q%destroy()
+
+ end if
+
+ n_instructions_group = get_group_entries_count_db(id)
+ n_instructions_total = get_available_count_db()
+
+ allocate(character( len=(n_instructions_total*384 + 512) ) :: res)
+
+ res = "<h2>"//trim(group_name)//"</h2>"
+
+ if(n_instructions_group == 0) then
+
+ res = trim(res)//new_line(' ')//"<p><em>Contains no instructions.</em></p>"
+
+ else
+
+ if(len_trim(launch_msg) > 0) then
+ res = trim(res)//new_line(' ')//'<p><strong>'//trim(launch_msg)//'</strong></p>'
+ else
+ res = trim(res)//new_line(' ')//'<p><a href="'//req%page//'?launch">&#x1f680; Launch Now</a></p>'
+ end if
+
+ res = trim(res)//new_line(' ')//"<h3>Work to Be Performed</h3>"//new_line(' ')//"<ul>"
+
+ entries => get_group_entries_db(id)
+ do i = 1, n_instructions_group
+
+ call get_instruction_name(entries(i)%instruction, instruction_name)
+ call get_player_name(entries(i)%player, player_name)
+
+ one_link => html_link("../instructions/"//trim(instruction_name)//".html", trim(instruction_name))
+ play_link => html_link("../players/"//trim(player_name)//".html", trim(player_name))
+ delete_link => html_link(trim(group_name)//".html?delete="// &
+ trim(instruction_name)//","//trim(player_name), &
+ "<em>Remove</em>")
+
+ res = trim(res)//new_line(' ')//"<li>"//one_link//" on "//play_link//" - "//delete_link//"</li>"
+
+ deallocate(one_link)
+ deallocate(play_link)
+ deallocate(delete_link)
+
+ end do
+
+ res = trim(res)//new_line(' ')//"</ul>"
+
+ end if
+
+ if(n_instructions_total > 0) then
+
+ res = trim(res)//new_line(' ')//"<h3>Add Instructions</h3>"
+
+ all_entries => get_available_work_pairs_db()
+ if(associated(all_entries)) then
+
+ res = trim(res)//new_line(' ')//'<form action="'//trim(group_name)//'.html" method="GET">'// &
+ '<label for="add">Instruction:</label>'//new_line(' ')// &
+ '<select name="add" id="add">'
+
+ do i=1,n_instructions_total
+
+ if(associated(entries)) then
+ if(any(entries%player == all_entries(i)%player .AND. &
+ entries%instruction == all_entries(i)%instruction) ) &
+ then
+ cycle
+ end if
+ end if
+
+ call get_instruction_name(all_entries(i)%instruction, instruction_name)
+ call get_player_name(all_entries(i)%player, player_name)
+ res = trim(res)//new_line(' ')//'<option value="'//trim(instruction_name)//","//trim(player_name)//'">'// &
+ trim(instruction_name)//" on "//trim(player_name)//"</option>"
+
+ end do
+
+ res = trim(res)//new_line(' ')//'</select>'//'<input type="submit" value="Add"/></form>'
+ end if
+ end if
+
+ res = trim(res)//new_line(' ')//'<h3>Destroy This Group</h3>'//new_line(' ')// &
+ '<p><a href="'//req%page//'?destroy">&#x1f4a3; Destroy</a></p>'//new_line(' ')// &
+ '<p><em>This operation will not destroy any instructions</em></p>'
+
+ end function generate_one_group_html
function generate_players_html() result(res)
use captain_db
@@ -694,7 +915,19 @@ contains
call page%assign('title', trim(job_page_title))
contents => generate_one_job_html(req)
call page%assign('contents', contents)
-
+
+ else if(trim(req%location) == "/groups.html") then
+
+ call page%assign('title', 'Instruction Groups')
+ contents => generate_groups_html(req)
+ call page%assign('contents', contents)
+
+ else if(trim(first) == "groups") then
+
+ call page%assign('title', 'Instruction Group')
+ contents => generate_one_group_html(req)
+ call page%assign('contents', contents)
+
else
call page%assign('title', 'Not Found')
@@ -716,7 +949,7 @@ contains
end function request_templated
function handle_post(req) result(resp)
- use captain_db, only: add_player_db
+ use captain_db, only: add_player_db, add_group_db
use page_template
use config, only: template_filepath
use logging
@@ -757,6 +990,18 @@ contains
end if
+ else if(trim(category) == "groups") then
+
+ call req%path_component(2, second)
+
+ ! Add a group
+ if(trim(second) == "add.html") then
+
+ call add_group_db(posted%get_value("name"))
+ call page%assign('destination', 'groups.html')
+
+ end if
+
end if
! Handle the template