aboutsummaryrefslogtreecommitdiff
path: root/player/endpoints.f90
diff options
context:
space:
mode:
Diffstat (limited to 'player/endpoints.f90')
-rw-r--r--player/endpoints.f9073
1 files changed, 17 insertions, 56 deletions
diff --git a/player/endpoints.f90 b/player/endpoints.f90
index 6a2c955..8c655d4 100644
--- a/player/endpoints.f90
+++ b/player/endpoints.f90
@@ -5,6 +5,7 @@ implicit none
character(*), parameter::LOCATION_STATUS = "/api/player/{name}/job/{jobid}/task/{step}"
character(*), parameter::LOCATION_JOB_COMPLETE = "/api/player/{name}/job/{jobid}/complete"
character(*), parameter::LOCATION_JOB_FAILED = "/api/player/{name}/job/{jobid}/failed"
+ character(*), parameter::LOCATION_INSTRUCTIONS = "/api/instruction/{name}"
integer, parameter::STATUS_STARTING=1
integer, parameter::STATUS_COMPLETED=2
@@ -16,11 +17,6 @@ implicit none
"failed ", &
"inprogress" /)
- interface replace_field
- module procedure replace_field_text
- module procedure replace_field_int
- end interface
-
contains
subroutine base_url(server, location, post, res)
@@ -39,59 +35,9 @@ contains
end subroutine base_url
- subroutine replace_field_text(str, field, val)
- implicit none
-
- character(*), intent(inout)::str
- character(*), intent(in)::field
- character(*), intent(in)::val
-
- character(len=:), allocatable::holding
- integer::length_estimate
- integer::field_location, i, j
-
- ! This is too big, but close enough
- length_estimate = len_trim(str) + len_trim(val)
- allocate(character(len=length_estimate) :: holding)
- holding = " "
-
- print *, trim(str)
-
- ! Find the field
- field_location = index(str, "{"//trim(field)//"}")
- if(field_location > 0) then
-
- i = field_location + len_trim(field) + 2
- holding = str(1:field_location-1)//trim(val)//str(i:len_trim(str))
-
- ! Put the results back now
- str = holding
-
- end if
-
- print *, trim(str)
-
- deallocate(holding)
-
- end subroutine replace_field_text
-
- subroutine replace_field_int(str, field, val)
- implicit none
-
- character(*), intent(inout)::str
- character(*), intent(in)::field
- integer, intent(in)::val
-
- character(16)::int_text
-
- write(int_text, *) val
-
- call replace_field_text(str, field, trim(adjustl(int_text)))
-
- end subroutine replace_field_int
-
subroutine get_check_in_url(res)
use config
+ use utilities, only: replace_field
implicit none
character(*), intent(out)::res
@@ -103,6 +49,7 @@ contains
subroutine get_status_url(job, step, url, posting, status)
use config
+ use utilities, only: replace_field
implicit none
integer, intent(in)::job
@@ -130,6 +77,7 @@ contains
subroutine get_job_report_url(job, success, res)
use config
+ use utilities, only: replace_field
implicit none
integer, intent(in)::job
@@ -146,4 +94,17 @@ contains
end subroutine get_job_report_url
+ subroutine get_instruction_url(instruction, url)
+ use config
+ use utilities, only: replace_field
+ implicit none
+
+ character(*), intent(in)::instruction
+ character(*), intent(out)::url
+
+ call base_url(captain, LOCATION_INSTRUCTIONS, .false., url)
+ call replace_field(url, "name", instruction)
+
+ end subroutine get_instruction_url
+
end module player_endpoints