! 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 external_handling implicit none contains function generate_jobs_gemini(req) result(res) use captain_db use server_response use request_utils, only: render_jobs_links 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 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 " linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n), .true.) 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 use special_filenames, only: get_task_result_static_filename use request_utils, only: get_status_utf8, get_player_link => player_link, & get_instruction_link => instruction_link implicit none type(request), intent(in)::req character(len=:), pointer::res character(4)::status integer::i, j, job_id type(job)::one_job character(1)::nl = new_line(' ') type(task), dimension(:), pointer::tasks character(32)::task_text, job_text character(len=:), pointer::task_results_filename character(len=:), pointer::player_link, instruction_link res => null() ! Ugh, all this nonsense call req%last_component(job_text) j = index(job_text, ".", back=.true.) job_text(j:len(job_text)) = " " read(job_text, '(I8)') 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 = "## Status - "//status player_link => get_player_link(one_job%player, .TRUE.) if(associated(player_link)) then res = trim(res)//nl//nl//"Running on:"//nl//player_link//nl//"Last update at: "//one_job%time deallocate(player_link) end if instruction_link => get_instruction_link(one_job%instruction, .TRUE.) if(associated(instruction_link)) then res = trim(res)//nl//"Executing:"//nl//instruction_link deallocate(instruction_link) end if 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) task_results_filename => get_task_result_static_filename(one_job%id, i, no_path=.true.) write(task_text, '(I8)') i res = trim(res)//nl//"=> /results/"//task_results_filename//" "// & 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_releases_gemini(req) result(res) use utilities use server_response use config implicit none type(request), intent(in)::req character(len=:), pointer::res character(len=DIR_LIST_STRING_LENGTH), dimension(:), pointer::directories character(len=DIR_LIST_STRING_LENGTH), dimension(:), pointer::files character(1024)::public_path, local_path, subpath integer::allocation_size, i character(1)::nl = new_line(' ') character(4)::folder_icon = char(240)//char(159)//char(147)//char(129) if(.not. associated(req%query_string)) then public_path = "/releases" local_path = release_dir else call combine_paths("/releases", req%query_string, public_path) call combine_paths(release_dir, req%query_string, local_path) end if res => null() ! Easy safety check - no relative paths if(index(local_path, '..') > 0) then allocate(character(len=64)::res) res = "None Found" return end if directories => get_directories_in_directory(local_path) files => get_files_in_directory(local_path) allocation_size = 1024 if(associated(directories)) then allocation_size = allocation_size + size(directories) * DIR_LIST_STRING_LENGTH end if if(associated(files)) then allocation_size = allocation_size + size(files) * DIR_LIST_STRING_LENGTH end if allocate(character(len=allocation_size) :: res) res = "## Listing for "//trim(public_path) ! Add an "Up" link if(trim(public_path) /= "/releases") then i = index(req%query_string, "/", back=.true.) if(i > 0) then res = trim(res)//nl//"=> /releases.gmi?"//req%query_string(1:(i-1))//" Up a directory" else res = trim(res)//nl//"=> /releases.gmi Up a directory" end if end if if(associated(directories)) then do i = 1, size(directories) if(associated(req%query_string)) then call combine_paths(req%query_string, trim(directories(i)), subpath) else subpath = trim(directories(i)) end if res = trim(res)//nl//"=> /releases.gmi?"//trim(subpath)//" "//folder_icon//" "//trim(directories(i)) end do deallocate(directories) end if if(associated(files)) then do i = 1, size(files) call combine_paths(public_path, trim(files(i)), subpath) res = trim(res)//nl//"=> "//trim(subpath)//" "//trim(files(i)) end do deallocate(files) end if end function generate_releases_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 use request_utils, only: get_status_utf8 use request_utils, only: render_jobs_links 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, gemini_mode=.true.) 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 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_instructions_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 use request_utils, only: handle_instruction_command 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" .or. req%location == "/releases.gmi") then ! Used for paging (jobs) or subdirs (releases) - 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_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_templated(req) result(resp) use page_template use config, only: template_filepath, project use logging use server_response use request_utils, only: get_job_page_title use utilities, only: build_date implicit none class(request), intent(in)::req type(response)::resp character(1024)::template_file type(template)::page character(len=:), pointer::contents character(64)::first, template_name character(128)::job_page_title ! Open the base template if(trim(req%location) == "/" .or. trim(req%location) == "/index.gmi") then template_name = "home.gmi" else if(trim(req%location) == "/about.gmi") then template_name = "about.gmi" else template_name = "index.gmi" end if call template_filepath(template_name, template_file) call page%init(trim(template_file)) call write_log("Processing request", LOG_INFO) call req%path_component(1, first) if(trim(req%location) == "/" .or. trim(req%location) == "/index.gmi") then call page%assign('title', 'Home') else if(trim(req%location) == "/releases.gmi") then call page%assign('title', 'Releases') contents => generate_releases_gemini(req) call page%assign('contents', contents) 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') call page%assign('build_date', build_date()) 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 if(trim(first) == "jobs") then call get_job_page_title(req, job_page_title) call page%assign('title', trim(job_page_title)) contents => generate_one_job_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", LOG_INFO) 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 use request_utils, only: is_request_static, request_static implicit none class(request), intent(in)::req type(response)::resp if(is_redirect_action(req)) then call write_log("Action request", LOG_INFO) resp = external_redirect_action_request_gemini(req) else if(is_input_provided_request(req)) then call write_log("Input request", LOG_INFO) resp = external_input_request_gemini(req) else if(is_input_required_request(req)) then call write_log("Input required", LOG_INFO) resp = external_input_required_gemini(req) else if(is_request_static(req)) then call write_log("Req static", LOG_INFO) resp = request_static(req) else call write_log("Req template", LOG_INFO) resp = external_request_templated(req) end if end function external_request_gemini function external_request_titan(req) result(resp) use server_response use special_filenames use query_utilities use security use logging implicit none type(titan_request), intent(in)::req type(response)::resp type(query)::q character(len=:), pointer::fullpath character(12)::job_text, task_text integer::job_id, task_num logical::proceed_to_create_filename character(64)::msg fullpath => null() proceed_to_create_filename = .false. proceed_to_create_filename = validate_titan_token(req%token) if(proceed_to_create_filename) then fullpath => get_full_filename_from_request(req) end if if(associated(fullpath)) then ! Write the file call write_log("Storing titan file to "//trim(fullpath), LOG_DEBUG) if(req%write_to(fullpath)) then resp%code = GEMINI_CODE_SUCCESS call resp%set_body_contents(RESPONSE_JSON_OKAY) resp%body_mimetype = "text/plain" else resp%code = GEMINI_CODE_TEMPFAIL end if else resp%code = GEMINI_CODE_PERMFAIL end if end function external_request_titan end module external_handling