aboutsummaryrefslogtreecommitdiff
path: root/player/instructions.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-24 16:41:09 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-24 16:41:09 -0400
commit5ca487daa2182f9ff6aa40b1a05dc3db6d0fc84f (patch)
tree0d29e4901a328741986b7bde9fee25ac9a539135 /player/instructions.f90
parentfb11ffeb2d98f239b20e618c65b8534b677957e9 (diff)
downloadlevitating-5ca487daa2182f9ff6aa40b1a05dc3db6d0fc84f.tar.gz
levitating-5ca487daa2182f9ff6aa40b1a05dc3db6d0fc84f.zip
Added concept of player identity. Started on the instructions processing loop.
Diffstat (limited to 'player/instructions.f90')
-rw-r--r--player/instructions.f9087
1 files changed, 83 insertions, 4 deletions
diff --git a/player/instructions.f90 b/player/instructions.f90
index 8c671c4..ce28413 100644
--- a/player/instructions.f90
+++ b/player/instructions.f90
@@ -99,6 +99,25 @@ contains
end function get_task_string
+ function get_task_logical(j, i, component, res) result(found)
+ use json_module
+ implicit none
+
+ class(json_file)::j
+ integer, intent(in)::i
+ character(*), intent(in)::component
+ logical, intent(out)::res
+ logical::found
+
+ character(len=64)::label
+ character(len=:), allocatable::json_string_value
+
+ call task_component(i, component, label)
+
+ call j%get(trim(label), res, found)
+
+ end function get_task_logical
+
subroutine get_task_name(j, i, description)
use json_module
implicit none
@@ -147,7 +166,9 @@ contains
character(32)::operation
character(256)::url
character(256)::filename
+ character(256)::branch
+ logical::destructive
logical, dimension(4)::found
call get_task_operation(j, i, operation)
@@ -176,23 +197,81 @@ contains
else if(trim(operation) == "git_update") then
capture_filename => generate_temporary_filename()
- found(1) = get_task_string(j, i, "url", url)
- found(2) = get_task_string(j, i, "filename", filename)
+ found(1) = get_task_string(j, i, "origin", url)
+ found(2) = get_task_string(j, i, "branch", branch)
+ found(3) = get_task_string(j, i, "directory", filename)
+ found(4) = get_task_logical(j, i, "destructive", destructive)
+ if(.not. found(4)) then
+ destructive = .false.
+ found(4) = .true.
+ end if
+
if(.not. all(found,1)) then
success = .false.
else
- success = download(url, filename)
+ success = git_update(url, branch, filename, destructive, capture_filename)
end if
else if(trim(operation) == "shell") then
+ capture_filename => generate_temporary_filename()
+ found(1) = get_task_string(j, i, "command", url)
+ found(2) = get_task_string(j, i, "directory", filename)
+
+ if(.not. all(found,1)) then
+ success = .false.
+ else
+ success = shell(command, directory, capture_filename)
+ end if
else if(trim(operation) == "delete_tree") then
-
+ found(1) = get_task_string(j, i, "directory", filename)
+
+ if(.not. all(found,1)) then
+ success = .false.
+ else
+ success = delete_tree(command, directory, capture_filename)
+ end if
end if
end function perform_task
+ subroutine perform_tasks(j)
+ use json_module
+ implicit none
+
+ class(json_file)::j
+ integer::task_count
+ integer::i
+ logical::res
+
+ character(len=:), pointer::captured_filename
+
+ task_count = get_task_count(j)
+
+ do i = 1, task_count
+
+ res = perform_task(j, i, captured_filename)
+
+ if(associated(captured_filename)) then
+ if(res) then
+
+ else
+
+ exit
+ endif
+ else
+ if(res) then
+
+ else
+
+ exit
+ endif
+ end if
+ end do
+
+ end subroutine perform_tasks
+
end module instructions \ No newline at end of file