module external_handling implicit none contains 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)//" " end select end function get_status_utf8 function render_jobs_links(jobs, startindex, stopindex) result(res) use captain_db implicit none type(job), dimension(:), pointer, intent(in)::jobs integer, intent(in), optional::startindex, stopindex character(len=:), pointer::res integer::nsize, i, first, last character(len=16)::int_text character(len=(2*PLAYER_NAME_LENGTH + 64))::link character(PLAYER_NAME_LENGTH)::player, instruction character(1)::nl = new_line(' ') 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) allocate(character(len=nsize) :: res) res = " " do i = first, last call get_instruction_name(jobs(i)%instruction, instruction) call get_player_name(jobs(i)%player, player) write(int_text, '(I8)') jobs(i)%id link = "=> jobs/"//trim(adjustl(int_text))//".gmi "// & trim(get_status_utf8(jobs(i)%status))//" Job "// & trim(adjustl(int_text))//" - "//trim(instruction) res = trim(res)//nl//nl//link res = trim(res)//nl//"Running on "//trim(player)// & " - Last Update: "//trim(jobs(i)%time) end do 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 function generate_jobs_gemini(req) result(res) use captain_db use server_response use logging implicit none type(request)::req character(len=:), pointer::res type(job), dimension(:), pointer::jobs integer::n, nsize integer::i_start_jobs, ierr character(len=:), pointer::linklist character(64)::dbgstr n = get_jobs_count() if(n == 0) then allocate(character(len=1024) :: res) res = "None Yet" else if(associated(req%query_string)) then read(req%query_string, *, iostat=ierr) i_start_jobs else ierr = -1 end if if(ierr /= 0) then i_start_jobs = 1 end if jobs => get_jobs() ! 15 per page nsize = 15*(2*PLAYER_NAME_LENGTH + 64) + 1024 allocate(character(len=nsize) :: res) res = "## Jobs " write(dbgstr, '(I3,1X,I3)') i_start_jobs, min(i_start_jobs+14, n) call write_log("Jobs between "//trim(dbgstr)) linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n)) res = trim(res)//trim(linklist) call write_log(linklist) deallocate(linklist) end if end function generate_jobs_gemini function generate_one_job_gemini(req) result(res) use captain_db use server_response implicit none type(request), intent(in)::req character(len=:), pointer::res character(4)::status integer::i, j, job_id type(job)::one_job character(PLAYER_NAME_LENGTH)::player character(1)::nl = new_line(' ') type(task), dimension(:), pointer::tasks character(16)::task_text, job_text res => null() i = index(req%location, "/", back=.true.) j = index(req%location, ".", back=.true.) job_text = req%location(i+1:j-1) read(job_text, *) job_id one_job = get_job(job_id) if(one_job%id >= 0) then allocate(character(len=1024) :: res) status = get_status_utf8(one_job%status) res = "## Job "//job_text//" - "//status call get_player_name(one_job%player, player) res = trim(res)//nl//nl//"Running on "//trim(player)//nl//"Last update at: "//one_job%time res = trim(res)//nl//nl//"### Task Results" tasks => get_job_tasks(job_id) if(associated(tasks)) then do i = 1, size(tasks) status = get_status_utf8(tasks(i)%status) write(task_text, '(I8)') tasks(i)%number res = trim(res)//nl//"=> /results/"//trim(job_text)//"-"//trim(adjustl(task_text))//".txt "// & trim(status)//"Task "//trim(adjustl(task_text)) end do deallocate(tasks) else res = trim(res)//nl//nl//"None reported yet" end if else allocate(character(len=64) :: res) write(res, '(A20, 1X, I5)') "No record of:", job_id end if end function generate_one_job_gemini function generate_players_gemini() result(res) use captain_db implicit none character(len=:), pointer::res character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::players integer::n, i, nsize character(len=3*PLAYER_NAME_LENGTH)::one_player n = get_player_count() if(n == 0) then allocate(character(len=1024) :: res) res = "None Yet" else players => get_player_names() nsize = 1024 do i = 1, size(players) nsize = nsize + 16 + 2*len_trim(players(i)) end do allocate(character(len=nsize) :: res) res = "## Existing Players" do i = 1, n one_player = "=> /players/"//trim(players(i))//".gmi "//trim(players(i)) if(i == 1) then res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//trim(one_player) else res = trim(res)//new_line(res(1:1))//trim(one_player) end if end do deallocate(players) end if res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//"## Management"// & new_line(res(1:1))//"=> /players/add.gmi Add Player" end function generate_players_gemini function generate_one_instuction_gemini(req) result(res) use captain_db use server_response implicit none type(request)::req character(len=:), pointer::res integer::id_from_req character(128)::instruction_name type(job), dimension(:), pointer::jobs integer, dimension(:), pointer::players character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::all_players integer::i, j, n_jobs, n_players, nsize character(len=:), pointer::job_link_text character(1)::nl = new_line(' ') character(PLAYER_NAME_LENGTH)::player_name character(4)::player_status i = index(req%location, "/", back=.true.) j = index(req%location, ".", back=.true.) instruction_name = req%location(i+1:j-1) id_from_req = get_instruction_id(trim(instruction_name)) jobs => get_jobs_for_instruction(id_from_req) if(associated(jobs)) then n_jobs = size(jobs) job_link_text => render_jobs_links(jobs) else n_jobs = 0 job_link_text => null() end if players => get_instruction_players(id_from_req) if(associated(players)) then n_players = size(players) else n_players = 0 end if nsize = 1024 if(n_jobs > 0) then nsize = nsize + len_trim(job_link_text) end if if(n_players > 0) then nsize = nsize + n_players*256 end if nsize = nsize + get_player_count()*(PLAYER_NAME_LENGTH+32) allocate(character(len=nsize) :: res) res = nl//"## "//trim(instruction_name) i = index(req%location, ".gmi", back=.true.) res = trim(res)//nl//"=> "//req%location(1:i-1)//".json View Raw" if(n_players == 0) then res = trim(res)//nl//nl//"No players currently can run these instructions" else res = trim(res)//nl//nl//"### Launch Now" do i = 1, n_players call get_player_name(players(i), player_name) if(is_player_busy(players(i))) then player_status = get_status_utf8(PLAYER_STATUS_BUSY) else player_status = get_status_utf8(PLAYER_STATUS_IDLE) end if res = trim(res)//nl//"=> "//trim(req%location)//"?launch="//trim(player_name)// & " "//trim(player_status)//" "//trim(player_name) end do end if res = trim(res)//nl//nl//"### Jobs" if(n_jobs == 0) then res = trim(res)//nl//"None Yet" else res = trim(res)//nl//job_link_text deallocate(job_link_text) end if all_players => get_player_names() if(associated(all_players)) then res = trim(res)//nl//nl//"### Assign"//nl//"Assign a player to these instructions" do i = 1, size(all_players) if(n_players > 0) then j = get_player_id(all_players(i)) if(any(j == players)) then cycle end if end if res = trim(res)//nl//"=> "//trim(req%location)//"?assign="//trim(all_players(i))// & " "//trim(all_players(i)) end do deallocate(all_players) end if if(n_players > 0) then res = trim(res)//nl//nl//"### Remove"//nl//"Remove a player from these instructions" do i = 1, n_players call get_player_name(players(i), player_name) res = trim(res)//nl//"=> "//trim(req%location)//"?remove="//trim(player_name)// & " "//trim(player_name) end do end if end function generate_one_instuction_gemini subroutine handle_instruction_command(req) use captain_db use server_response use remote_launch implicit none type(request), intent(in)::req character(32)::command character(PLAYER_NAME_LENGTH)::argument, instruction_name integer::i, j i = index(req%location, "/", back=.true.) j = index(req%location, ".", back=.true.) instruction_name = req%location(i+1:j-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") then call launch_instructions_on_player(instruction_name, argument) else if(trim(command) == "assign") 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") 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 function generate_instructions_gemini() result(res) use captain_db implicit none character(len=:), pointer::res character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::instruction_names integer::n, i, nsize character(len=3*PLAYER_NAME_LENGTH)::one_player n = get_instuctions_count() if(n == 0) then allocate(character(len=1024) :: res) res = "None Yet" else instruction_names => get_instruction_names() nsize = 1024 do i = 1, size(instruction_names) nsize = nsize + 16 + 2*len_trim(instruction_names(i)) end do allocate(character(len=nsize) :: res) res = "## Instructions" do i = 1, n one_player = "=> /instructions/"//trim(instruction_names(i))//".gmi "//trim(instruction_names(i)) if(i == 1) then res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//trim(one_player) else res = trim(res)//new_line(res(1:1))//trim(one_player) end if end do deallocate(instruction_names) end if res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//"## Management"// & new_line(res(1:1))//"=> /instructions/scan.gmi Scan for Instructions" end function generate_instructions_gemini pure function is_input_provided_request(req) use server_response, only: request implicit none class(request), intent(in)::req logical::is_input_provided_request is_input_provided_request = associated(req%query_string) end function is_input_provided_request pure function is_input_required_request(req) use server_response, only: request implicit none class(request), intent(in)::req logical::is_input_required_request is_input_required_request = .false. if(req%location == "/players/add.gmi") then is_input_required_request = .true. end if end function is_input_required_request function external_input_required_gemini(req) result(resp) use server_response implicit none class(request), intent(in)::req type(response)::resp resp%code = GEMINI_CODE_INPUT if(req%location == "/players/add.gmi") then call resp%set_message("Enter name of new player to add") end if end function external_input_required_gemini function external_input_request_gemini(req) result(resp) use server_response use captain_db implicit none class(request), intent(in)::req type(response)::resp character(64)::first call req%path_component(1, first) if(req%location == "/players/add.gmi") then call add_player_db(req%query_string) resp%code = GEMINI_CODE_REDIRECT call resp%set_url("/players.gmi") else if(req%location == "/jobs.gmi") then ! Used for paging - send it back resp = external_request_templated(req) else if(trim(first) == "instructions") then ! Instruction command call handle_instruction_command(req) ! Go back to the same location resp%code = GEMINI_CODE_REDIRECT call resp%set_url(req%location) end if end function external_input_request_gemini 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)) 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 is_redirect_action(req) use server_response implicit none class(request), intent(in)::req logical::is_redirect_action is_redirect_action = .false. if(req%location == "/instructions/scan.gmi") then is_redirect_action = .true. end if end function is_redirect_action function external_redirect_action_request_gemini(req) result(resp) use captain_db use server_response use logging implicit none class(request), intent(in)::req type(response)::resp resp%code = GEMINI_CODE_REDIRECT if(req%location == "/instructions/scan.gmi") then call scan_instructions_for_db() call resp%set_url("/instructions.gmi") end if end function external_redirect_action_request_gemini function external_request_static(req) result(resp) use logging, only: write_log 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. resp%body_filename => get_special_full_filename(category, filename) inquire(file=resp%body_filename, exist=exists) if(.not. exists) then resp%code = GEMINI_CODE_PERMFAIL call write_log("File did not exist: "//resp%body_filename) else resp%code = GEMINI_CODE_SUCCESS if(index(filename, ".gmi") /= 0) then resp%body_mimetype = "text/gemini" else if(index(filename, ".txt") /= 0) then resp%body_mimetype = "text/plain" else if(index(filename, ".json") /= 0) then resp%body_mimetype = "text/plain" ! Just a catch-all, whatever... else resp%body_mimetype = "application/octet-stream" end if end if end function external_request_static function external_request_templated(req) result(resp) use page_template use config, only: template_filepath, project use logging, only: write_log use server_response implicit none class(request), intent(in)::req type(response)::resp character(1024)::template_file type(template)::page character(len=:), pointer::contents character(64)::first ! Open the base template call template_filepath("index.gmi", template_file) call page%init(trim(template_file)) call write_log("Processing request") call req%path_component(1, first) if(trim(req%location) == "/" .or. trim(req%location) == "/index.gmi") then call write_log("Assign") call page%assign('title', 'Home') call write_log("Assign done") else if(trim(req%location) == "/releases.gmi") then call page%assign('title', 'Releases') else if(trim(req%location) == "/jobs.gmi") then call page%assign('title', 'Jobs') contents => generate_jobs_gemini(req) call page%assign('contents', contents) else if(trim(req%location) == "/players.gmi") then call page%assign('title', 'Players') contents => generate_players_gemini() call page%assign('contents', contents) else if(req%location(1:9) == '/players/') then else if(trim(req%location) == "/about.gmi") then call page%assign('title', 'About') else if(trim(req%location) == "/instructions.gmi") then call page%assign('title', 'Build Instructions') contents => generate_instructions_gemini() call page%assign('contents', contents) else if(trim(first) == "instructions") then call page%assign('title', 'Build Instructions') contents => generate_one_instuction_gemini(req) call page%assign('contents', contents) else call page%assign('title', 'Not Found') end if call page%assign('project', project) call write_log("Rendering page for "//req%location) call page%render() call write_log("Finalizing response") resp%temporary_file = .true. resp%body_filename => page%output_filename resp%body_mimetype = "text/gemini" resp%code = GEMINI_CODE_SUCCESS end function external_request_templated function external_request_gemini(req) result(resp) use server_response use logging implicit none class(request), intent(in)::req type(response)::resp if(is_redirect_action(req)) then call write_log("Action request") resp = external_redirect_action_request_gemini(req) else if(is_input_provided_request(req)) then call write_log("Input request") resp = external_input_request_gemini(req) else if(is_input_required_request(req)) then call write_log("Input required") resp = external_input_required_gemini(req) else if(is_request_static(req)) then call write_log("Req static") resp = external_request_static(req) else call write_log("Req template") resp = external_request_templated(req) end if end function external_request_gemini end module external_handling