aboutsummaryrefslogtreecommitdiff
path: root/player/instructions.f90
diff options
context:
space:
mode:
Diffstat (limited to 'player/instructions.f90')
-rw-r--r--player/instructions.f9075
1 files changed, 67 insertions, 8 deletions
diff --git a/player/instructions.f90 b/player/instructions.f90
index ce28413..fed43c4 100644
--- a/player/instructions.f90
+++ b/player/instructions.f90
@@ -24,6 +24,22 @@ contains
end subroutine destroy_instructions
+ function work_available(j)
+ use json_module
+ implicit none
+
+ class(json_file)::j
+ logical::work_available
+
+ character(len=:), allocatable::json_string_value
+ logical::found
+
+ call j%get("idle", json_string_value, found)
+
+ work_available = .not. found
+
+ end function work_available
+
subroutine get_description(j, description)
use json_module
implicit none
@@ -42,6 +58,22 @@ contains
end subroutine get_description
+ function get_job_id(j) result(id)
+ use json_module
+ implicit none
+
+ class(json_file)::j
+ integer::id
+
+ logical::found
+
+ call j%get("id", id, found)
+ if(.not. found) then
+ id = -1
+ end if
+
+ end function get_job_id
+
function get_task_count(j) result(n)
use json_module
implicit none
@@ -167,6 +199,7 @@ contains
character(256)::url
character(256)::filename
character(256)::branch
+ character(256)::cmd
logical::destructive
logical, dimension(4)::found
@@ -216,13 +249,13 @@ contains
else if(trim(operation) == "shell") then
capture_filename => generate_temporary_filename()
- found(1) = get_task_string(j, i, "command", url)
+ found(1) = get_task_string(j, i, "command", cmd)
found(2) = get_task_string(j, i, "directory", filename)
if(.not. all(found,1)) then
success = .false.
else
- success = shell(command, directory, capture_filename)
+ success = shell(cmd, filename, capture_filename)
end if
else if(trim(operation) == "delete_tree") then
@@ -231,7 +264,7 @@ contains
if(.not. all(found,1)) then
success = .false.
else
- success = delete_tree(command, directory, capture_filename)
+ success = delete_tree(filename)
end if
end if
@@ -240,38 +273,64 @@ contains
subroutine perform_tasks(j)
use json_module
+ use talking
+ use player_endpoints
+ use utilities, only: delete_file
implicit none
class(json_file)::j
+
integer::task_count
integer::i
+ integer::server_status
logical::res
-
+ integer::job_id
character(len=:), pointer::captured_filename
+ character(len=1024)::url
task_count = get_task_count(j)
+ job_id = get_job_id(j)
do i = 1, task_count
+ call get_status_url(job_id, i, url, status=STATUS_STARTING)
+ server_status = request_to_ignored(url)
+
res = perform_task(j, i, captured_filename)
if(associated(captured_filename)) then
if(res) then
-
+ call get_status_url(job_id, i, url, status=STATUS_COMPLETED)
+ server_status = request_to_ignored(url)
+
+ call get_status_url(job_id, i, url, posting=.true.)
+ server_status = send_file(url, captured_filename)
+
+ ! Get rid of the local file
+ call delete_file(captured_filename)
+ deallocate(captured_filename)
+ captured_filename => null()
else
-
+ call get_status_url(job_id, i, url, status=STATUS_FAILED)
+ server_status = request_to_ignored(url)
exit
endif
+
else
if(res) then
-
+ call get_status_url(job_id, i, url, status=STATUS_COMPLETED)
+ server_status = request_to_ignored(url)
else
-
+ call get_status_url(job_id, i, url, status=STATUS_FAILED)
+ server_status = request_to_ignored(url)
exit
endif
end if
end do
+ call get_job_report_url(job_id, res, url)
+ server_status = request_to_ignored(url)
+
end subroutine perform_tasks
end module instructions \ No newline at end of file