From fb11ffeb2d98f239b20e618c65b8534b677957e9 Mon Sep 17 00:00:00 2001 From: Jeffrey Armstrong Date: Wed, 24 Mar 2021 14:58:32 -0400 Subject: Initial import --- player/instructions.f90 | 198 ++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 198 insertions(+) create mode 100644 player/instructions.f90 (limited to 'player/instructions.f90') diff --git a/player/instructions.f90 b/player/instructions.f90 new file mode 100644 index 0000000..8c671c4 --- /dev/null +++ b/player/instructions.f90 @@ -0,0 +1,198 @@ +module instructions +implicit none + +contains + + function parse_instructions(filename) result(j) + use json_module + implicit none + + type(json_file)::j + character(*), intent(in)::filename + + call j%initialize() + call j%load_file(filename=filename) + + end function parse_instructions + + subroutine destroy_instructions(j) + use json_module + implicit none + + type(json_file)::j + call j%destroy() + + end subroutine destroy_instructions + + subroutine get_description(j, description) + use json_module + implicit none + + class(json_file)::j + character(*), intent(out)::description + character(len=:), allocatable::json_string_value + logical::found + + call j%get("description", json_string_value, found) + if(.not. found .or. .not. allocated(json_string_value)) then + description = "(instructions)" + else + description = json_string_value + end if + + end subroutine get_description + + function get_task_count(j) result(n) + use json_module + implicit none + + class(json_file)::j + integer::n + + type(json_value), pointer ::server + logical::found + character(3)::index_string + n = 0 + + found = .true. + do while(found) + n = n + 1 + write(index_string, '(I3)') n + call j%get("tasks("//trim(index_string)//")", server, found) + end do + n = n - 1 + + end function get_task_count + + pure subroutine task_component(i, component, label) + implicit none + + integer, intent(in)::i + character(*), intent(in)::component + character(*), intent(out)::label + + write(label, '(A6,I3,A2)') "tasks(", i, ")." + label = label//trim(component) + + end subroutine task_component + + function get_task_string(j, i, component, res) result(found) + use json_module + implicit none + + class(json_file)::j + integer, intent(in)::i + character(*), intent(in)::component + character(*), 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), json_string_value, found) + + if(allocated(json_string_value)) then + res = json_string_value + end if + + end function get_task_string + + subroutine get_task_name(j, i, description) + use json_module + implicit none + + class(json_file)::j + character(*), intent(out)::description + integer, intent(in)::i + logical::found + + found = get_task_string(j, i, "name", description) + + if(.not. found) then + write(description, '(A4, 1X, I3)') "Task", i + end if + + end subroutine get_task_name + + subroutine get_task_operation(j, i, op) + use json_module + implicit none + + class(json_file)::j + character(*), intent(out)::op + integer, intent(in)::i + logical::found + + found = get_task_string(j, i, "operation", op) + + if(.not. found) then + op = " " + end if + + end subroutine get_task_operation + + function perform_task(j, i, capture_filename) result(success) + use json_module + use tasks + use utilities + implicit none + + class(json_file)::j + integer, intent(in)::i + character(len=:), pointer, intent(out)::capture_filename + logical::success + + character(32)::operation + character(256)::url + character(256)::filename + + logical, dimension(4)::found + + call get_task_operation(j, i, operation) + + found = .true. + capture_filename => null() + + if(trim(operation) == "upload") then + found(1) = get_task_string(j, i, "url", url) + found(2) = get_task_string(j, i, "filename", filename) + if(.not. all(found,1)) then + success = .false. + else + success = upload(url, filename) + end if + + else if(trim(operation) == "download") then + found(1) = get_task_string(j, i, "url", url) + found(2) = get_task_string(j, i, "filename", filename) + if(.not. all(found,1)) then + success = .false. + else + success = download(url, filename) + end if + + 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) + if(.not. all(found,1)) then + success = .false. + else + success = download(url, filename) + end if + + + else if(trim(operation) == "shell") then + + + else if(trim(operation) == "delete_tree") then + + + end if + + end function perform_task + +end module instructions \ No newline at end of file -- cgit v1.2.3