! Copyright (c) 2021 Approximatrix, LLC ! ! Permission is hereby granted, free of charge, to any person obtaining a copy ! of this software and associated documentation files (the "Software"), to deal ! in the Software without restriction, including without limitation the rights ! to use, copy, modify, merge, publish, distribute, sublicense, and/or sell ! copies of the Software, and to permit persons to whom the Software is ! furnished to do so, subject to the following conditions: ! ! The above copyright notice and this permission notice shall be included in ! all copies or substantial portions of the Software. ! ! The Software shall be used for Good, not Evil. ! ! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR ! IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, ! FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE ! AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER ! LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, ! OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE ! SOFTWARE. module player_endpoints implicit none character(*), parameter::LOCATION_CHECK_IN = "/api/player/{name}/checkin.json" 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 integer, parameter::STATUS_FAILED=3 integer, parameter::STATUS_IN_PROGRESS=4 character(len=10), dimension(4)::status_text = (/ "starting ", & "complete ", & "failed ", & "inprogress" /) contains subroutine base_url(server, location, post, res) implicit none character(*), intent(in)::server character(*), intent(in)::location logical, intent(in)::post character(*), intent(out)::res if(post) then res = "titan://"//trim(server)//trim(location) else res = "gemini://"//trim(server)//trim(location) end if end subroutine base_url subroutine append_query_token(url) use config, only: token implicit none character(len=*), intent(inout)::url character::prepend if(len_trim(token) > 0) then if(index(url, "?") > 0) then prepend = "&" else prepend = "?" end if url = trim(url)//prepend//"token="//trim(token) end if end subroutine append_query_token subroutine get_check_in_url(res) use config use utilities, only: replace_field implicit none character(*), intent(out)::res call base_url(captain, LOCATION_CHECK_IN, .false., res) call replace_field(res, "name", identity) call append_query_token(res) end subroutine get_check_in_url subroutine get_status_url(job, step, url, posting, status, task_type) use config use utilities, only: replace_field implicit none integer, intent(in)::job integer, intent(in)::step logical, intent(in), optional::posting integer, intent(in), optional::status character(len=*), intent(in), optional::task_type character(*), intent(out)::url logical::internal_posting internal_posting = .false. if(present(posting)) then internal_posting = posting end if call base_url(captain, LOCATION_STATUS, internal_posting, url) call replace_field(url, "name", identity) call replace_field(url, "jobid", job) call replace_field(url, "step", step) ! Query strings aren't to be used when posting (i.e. a titan request) if(.not. internal_posting) then if(present(status)) then url = trim(url)//"?status="//trim(status_text(status)) if(present(task_type)) then url = trim(url)//"&type="//trim(task_type) end if else if(present(task_type)) then url = trim(url)//"?type="//trim(task_type) end if call append_query_token(url) end if end subroutine get_status_url subroutine get_job_report_url(job, success, res) use config use utilities, only: replace_field implicit none integer, intent(in)::job logical, intent(in)::success character(*), intent(out)::res if(success) then call base_url(captain, LOCATION_JOB_COMPLETE, .false., res) else call base_url(captain, LOCATION_JOB_FAILED, .false., res) end if call replace_field(res, "name", identity) call replace_field(res, "jobid", job) call append_query_token(res) 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