! 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 request_utils implicit none interface player_link module procedure player_link_from_name module procedure player_link_from_id end interface interface instruction_link module procedure instruction_link_from_name module procedure instruction_link_from_id end interface interface get_player_status_utf8 module procedure get_player_status_utf8_by_id module procedure get_player_status_utf8_by_name end interface contains pure function success_code(req) use http_codes, only: HTTP_SUCCESS => HTTP_CODE_SUCCESS use gemini_codes, only: GEMINI_SUCCESS => GEMINI_CODE_SUCCESS use server_response, only: request implicit none class(request), intent(in)::req integer::success_code if(req%protocol == 'gemini') then success_code = GEMINI_SUCCESS else success_code = HTTP_SUCCESS end if end function success_code pure function notfound_code(req) use http_codes, only: HTTP_FAIL => HTTP_CODE_NOTFOUND use gemini_codes, only: GEMINI_FAIL => GEMINI_CODE_PERMFAIL use server_response, only: request implicit none class(request), intent(in)::req integer::notfound_code if(req%protocol == 'gemini') then notfound_code = GEMINI_FAIL else notfound_code = HTTP_FAIL end if end function notfound_code pure function notpermitted_code(req) use http_codes, only: HTTP_UNAUTHORIZED => HTTP_CODE_UNAUTHORIZED use gemini_codes, only: GEMINI_UNAUTHORIZED => GEMINI_CODE_BAD_REQUEST use server_response, only: request implicit none class(request), intent(in)::req integer::notpermitted_code if(req%protocol == 'gemini') then ! You might think we'd use Gemini certificates, but fuck certificates... ! Just fail with a bad request. notpermitted_code = GEMINI_UNAUTHORIZED else notpermitted_code = HTTP_UNAUTHORIZED end if end function notpermitted_code subroutine basic_mimetype(actual_filename, mimetype) use utilities, only: get_one_line_output_shell_command implicit none character(*), intent(in)::actual_filename character(*), intent(out)::mimetype logical::exists ! Check for gemini first since it's fake... if(index(actual_filename, ".gmi") /= 0) then mimetype = "text/gemini" else inquire(file=actual_filename, exist=exists) if(exists) then call get_one_line_output_shell_command("mimetype -b "//trim(actual_filename), mimetype) else ! If it doesn't exist, use the extension dumbly if(index(actual_filename, ".txt") /= 0) then mimetype = "text/plain" else if(index(actual_filename, ".json") /= 0) then mimetype = "text/plain" else if(index(actual_filename, ".html") /= 0) then mimetype = "text/html" else if(index(actual_filename, ".css") /= 0) then mimetype = "text/css" ! Just a catch-all, whatever... else mimetype = "application/octet-stream" end if end if end if end subroutine basic_mimetype pure function get_status_utf8(status) result(res) use captain_db implicit none integer, intent(in)::status character(4)::res select case(status) case(JOB_STATUS_SUCCESS) ! Check mark 0x2714 res = char(226)//char(156)//char(148)//" " case(JOB_STATUS_FAILURE) ! Ballot x 0x2717 res = char(226)//char(156)//char(151)//" " case(JOB_STATUS_WORKING) ! Runner 0x1f3c3 res = char(240)//char(159)//char(143)//char(131) case(PLAYER_STATUS_IDLE) ! Sleeping 0x1f4a4 res = char(240)//char(159)//char(146)//char(164) case(JOB_STATUS_PENDING) ! Envelope 0x2709 res = char(226)//char(156)//char(137)//" " case(PLAYER_STATUS_OFFLINE) ! Fancy question mark 0xe29d93 res = char(226)//char(157)//char(147)//" " end select end function get_status_utf8 function get_player_status_utf8_by_id(player_id) result(res) use captain_db, only: is_player_online, is_player_busy, & PLAYER_STATUS_BUSY, PLAYER_STATUS_IDLE, PLAYER_STATUS_OFFLINE implicit none integer, intent(in)::player_id character(4)::res if(is_player_online(player_id)) then if(is_player_busy(player_id)) then res = get_status_utf8(PLAYER_STATUS_BUSY) else res = get_status_utf8(PLAYER_STATUS_IDLE) end if else res = get_status_utf8(PLAYER_STATUS_OFFLINE) end if end function get_player_status_utf8_by_id function get_player_status_utf8_by_name(player) result(res) use captain_db, only: get_player_id implicit none character(*), intent(in)::player character(4)::res res = get_player_status_utf8_by_id(get_player_id(player)) end function get_player_status_utf8_by_name function is_request_static(req) use server_response use logging implicit none class(request), intent(in)::req logical::is_request_static character(64)::first, last character(4)::ext integer::j call req%path_component(1, first) call req%last_component(last) j = index(last, ".", back=.true.) if(j > 0) then ext = last(j+1:len_trim(last)) else ext = " " end if call write_log("Static check: "//trim(first), LOG_DEBUG) is_request_static = ((trim(first) == "releases") .or. & (trim(first) == "uploads") .or. & (trim(first) == "results") .or. & (trim(first) == "static") .or. & (trim(first) == "favicon.txt") .or. & (trim(first) == "instructions" .and. trim(ext) == "json")) end function is_request_static function request_static(req) result(resp) use logging use config use utilities use server_response use special_filenames implicit none class(request), intent(in)::req type(response)::resp character(64)::category character(256)::filename logical::exists resp%temporary_file = .false. call req%path_component(1, category) call req%path_starting_with_component(2, filename) if((req%auth_level < global_permissions%get("view-raw-instructions") .and. trim(category) == "instructions") .or. & (req%auth_level < global_permissions%get("access-releases") .and. trim(category) == "releases") .or. & (req%auth_level < global_permissions%get("access-logs") .and. trim(category) == "results")) & then resp%code = notpermitted_code(req) else resp%body_filename => get_special_full_filename(trim(category), trim(filename)) inquire(file=resp%body_filename, exist=exists) if(.not. exists) then resp%code = notfound_code(req) call write_log("File did not exist: "//resp%body_filename, LOG_NORMAL) else resp%code = success_code(req) call basic_mimetype(resp%body_filename, resp%body_mimetype) end if end if end function request_static function build_link(link, label, gemini_mode, session_token) result(res) use server_response, only: gemini_session_link_url implicit none character(*), intent(in)::link, label logical, intent(in)::gemini_mode ! Passed in to prepend a session identifier in gemini character(len=:), pointer, intent(in), optional::session_token character(len=:), pointer::res character(len=:), pointer::gemlink integer::nl if(gemini_mode) then if(present(session_token)) then gemlink => gemini_session_link_url(link, session_token) else gemlink => gemini_session_link_url(link, null()) end if nl = len_trim(gemlink) + len_trim(label) + len('=> ') allocate(character(len=nl)::res) res = '=> '//trim(gemlink)//' '//trim(label) else nl = len_trim(link) + len_trim(label) + len('') allocate(character(len=nl)::res) res = ''//trim(label)//'' end if end function build_link function element_link_from_name(n, category, gemini_mode, prefix) result(res) implicit none character(*), intent(in)::n, category logical, intent(in)::gemini_mode character(*), intent(in), optional::prefix character(len=:), pointer::res character(256)::dest if(present(prefix)) then dest = prefix if(dest(len_trim(dest):len_trim(dest)) /= '/') then dest = trim(dest)//"/" end if else dest = "/" end if dest = trim(dest)//trim(category)//"/"//trim(n) if(gemini_mode) then dest = trim(dest)//".gmi" else dest = trim(dest)//".html" end if res => build_link(trim(dest), trim(n), gemini_mode) end function element_link_from_name function player_link_from_name(n, gemini_mode, prefix) result(res) implicit none character(*), intent(in)::n logical, intent(in)::gemini_mode character(*), intent(in), optional::prefix character(64)::internal_prefix character(len=:), pointer::res if(present(prefix)) then internal_prefix = prefix else internal_prefix = "/" end if res => element_link_from_name(n, "players", gemini_mode, internal_prefix) end function player_link_from_name function player_link_from_id(id, gemini_mode, prefix) result(res) use captain_db, only: PLAYER_NAME_LENGTH, get_player_name implicit none integer, intent(in)::id logical, intent(in)::gemini_mode character(*), intent(in), optional::prefix character(len=:), pointer::res character(64)::internal_prefix character(PLAYER_NAME_LENGTH)::name if(present(prefix)) then internal_prefix = prefix else internal_prefix = "/" end if name = " " call get_player_name(id, name) res => player_link_from_name(name, gemini_mode, internal_prefix) end function player_link_from_id function instruction_link_from_name(n, gemini_mode, prefix) result(res) implicit none character(*), intent(in)::n logical, intent(in)::gemini_mode character(*), intent(in), optional::prefix character(64)::internal_prefix character(len=:), pointer::res if(present(prefix)) then internal_prefix = prefix else internal_prefix = "/" end if res => element_link_from_name(n, "instructions", gemini_mode, internal_prefix) end function instruction_link_from_name function instruction_link_from_id(id, gemini_mode, prefix) result(res) use captain_db, only: PLAYER_NAME_LENGTH, get_instruction_name implicit none integer, intent(in)::id logical, intent(in)::gemini_mode character(*), intent(in), optional::prefix character(len=:), pointer::res character(64)::internal_prefix character(PLAYER_NAME_LENGTH)::name if(present(prefix)) then internal_prefix = prefix else internal_prefix = "/" end if name = " " call get_instruction_name(id, name) res => instruction_link_from_name(name, gemini_mode, internal_prefix) end function instruction_link_from_id function generate_simple_pager(startindex, stopindex, step, maxcount, page, gemini_mode) result(res) use logging implicit none integer, intent(in)::startindex, stopindex, step, maxcount character(*), intent(in)::page logical, intent(in)::gemini_mode character(len=:), pointer::res integer::i character(len=:), allocatable::back_page, forward_page character(len=:), pointer::back_link, forward_link character(5)::num integer::res_size res_size = 128 back_link => null() forward_link => null() if(startindex > 1) then i = max(startindex-step, 1) allocate(character(len=(len_trim(page)+6)) :: back_page) write(num, '(I5)') i num = adjustl(num) back_page = trim(page)//"?"//trim(num) back_link => build_link(back_page, "Newer", gemini_mode) deallocate(back_page) end if if(stopindex < maxcount) then i = stopindex+1 allocate(character(len=(len_trim(page)+6)) :: forward_page) write(num, '(I5)') i num = adjustl(num) forward_page = trim(page)//"?"//trim(num) forward_link => build_link(forward_page, "Older", gemini_mode) deallocate(forward_page) end if if(.not. associated(back_link) .and. .not. associated(forward_link)) then res => null() else if(gemini_mode) then res_size = 1 else res_size = len('

-

') end if if(associated(back_link)) then res_size = res_size + len(back_link) end if if(associated(forward_link)) then res_size = res_size + len(forward_link) end if allocate(character(len=res_size) :: res) res = " " if(gemini_mode) then if(associated(back_link)) then res = back_link deallocate(back_link) end if if(associated(forward_link)) then if(len_trim(res) > 0) then res = trim(res)//new_line(' ')//forward_link else res = forward_link end if deallocate(forward_link) end if else if(associated(back_link)) then res = '

'//back_link deallocate(back_link) end if if(associated(forward_link)) then if(len_trim(res) > 0) then res = trim(res)//" - "//forward_link else res = '

'//forward_link end if deallocate(forward_link) end if res = trim(res)//"

" end if end if end function generate_simple_pager function render_jobs_links(jobs, startindex, stopindex, gemini_mode, link_prefix, session_token) result(res) use captain_db implicit none type(job), dimension(:), pointer, intent(in)::jobs integer, intent(in), optional::startindex, stopindex logical, intent(in)::gemini_mode character(*), intent(in), optional::link_prefix character(len=:), intent(in), pointer, optional::session_token character(len=:), pointer::res integer::nsize, i, first, last character(len=16)::int_text character(len=(2*PLAYER_NAME_LENGTH + 64))::link character(len=:), pointer::link_pointer character(len=:), pointer::internal_session_token character(PLAYER_NAME_LENGTH)::player, instruction character(1)::nl = new_line(' ') character(64)::int_link_prefix if(present(link_prefix)) then int_link_prefix = link_prefix else int_link_prefix = " " end if if(present(session_token)) then internal_session_token => session_token else internal_session_token => null() end if if(.not. associated(jobs)) then allocate(character(len=32)::res) res = "None Yet" else first = 1 if(present(startindex)) then first = startindex end if last = size(jobs) if(present(stopindex)) then last = min(size(jobs), stopindex) end if if(first <= last .and. first <= size(jobs)) then nsize = (last-first+1)*(2*PLAYER_NAME_LENGTH + 64) + 32 allocate(character(len=nsize) :: res) if(gemini_mode) then res = " " else res ='" end if else ! Indices exceed array allocate(character(len=64)::res) write(int_text, '(I8)') first res = "None at index "//trim(adjustl(int_text))//" or beyond" end if end if end function render_jobs_links subroutine get_job_page_title(req, title) use captain_db use server_response implicit none type(request), intent(in)::req character(*), intent(out)::title integer::job_id, i character(32)::job_text character(PLAYER_NAME_LENGTH)::instruction_name ! All this to get the job id call req%last_component(job_text) i = index(job_text, ".") job_text(i:len(job_text)) = " " read(job_text, '(I8)') job_id ! Request instruction name i = get_job_instruction(job_id) call get_instruction_name(i, instruction_name) title = "Job "//trim(job_text)//" - "//trim(instruction_name) end subroutine get_job_page_title subroutine handle_instruction_command(req) use captain_db use server_response use remote_launch use config, only: global_permissions implicit none type(request), intent(in)::req character(32)::command character(PLAYER_NAME_LENGTH)::argument, instruction_name integer::i, j i = index(req%page, ".", back=.true.) instruction_name = req%page(1:i-1) i = index(req%query_string, "=") command = req%query_string(1:i-1) argument = req%query_string(i+1:len_trim(req%query_string)) if(trim(command) == "launch" .and. req%auth_level >= global_permissions%get("launch-job")) then call launch_instructions_on_player(instruction_name, argument) else if(trim(command) == "assign" .and. req%auth_level >= global_permissions%get("assign-instructions")) then i = get_instruction_id(trim(instruction_name)) j = get_player_id(trim(argument)) call add_player_for_instruction(i, j) else if(trim(command) == "remove" .and. req%auth_level >= global_permissions%get("assign-instructions")) then i = get_instruction_id(trim(instruction_name)) j = get_player_id(trim(argument)) call remove_player_for_instruction(i, j) end if end subroutine handle_instruction_command end module request_utils