module web implicit none private public :: handle_request integer, parameter::REQUEST_UNKNOWN = 0 integer, parameter::REQUEST_GET = 1 integer, parameter::REQUEST_POST = 2 contains function method() use utilities, only: toupper implicit none integer::method character(4)::method_text call get_environment_variable("REQUEST_METHOD", method_text) call toupper(method_text) if(trim(method_text) == "GET") then method = REQUEST_GET else if(method_text == "POST") then method = REQUEST_POST else method = REQUEST_UNKNOWN end if end function method subroutine build_request_object(req) use server_response, only:request type(request), intent(out)::req character(len=:), allocatable::url, script_name integer::url_size call get_environment_variable("REQUEST_URI", length=url_size) allocate(character(len=url_size)::url, script_name) call get_environment_variable("REQUEST_URI", url) call get_environment_variable("SCRIPT_NAME", script_name) ! If we're in CGI mode, treat the "server" as the script name call req%init(url, server_explicit=script_name, protocol_explicit="http") deallocate(url) deallocate(script_name) end subroutine build_request_object function html_link(link, label) result(res) implicit none character(*), intent(in)::link, label character(len=:), pointer::res integer::nl nl = len_trim(link) + len_trim(label) + len('') allocate(character(len=nl)::res) res = ''//trim(label)//'' end function html_link function generate_releases_html(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) character(len=:), pointer::one_link if(.not. associated(req%query_string)) then public_path = "/releases" local_path = release_dir else if(len_trim(req%query_string) == 0) 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 + 2 * size(directories) * (DIR_LIST_STRING_LENGTH+32) end if if(associated(files)) then allocation_size = allocation_size + 2 * size(files) * (DIR_LIST_STRING_LENGTH+32) end if allocate(character(len=allocation_size) :: res) res = "

Listing for "//trim(public_path)//"

"//nl//"" end function generate_releases_html function generate_jobs_html(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 character(10)::pager 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 = " " linklist => render_jobs_links(jobs, i_start_jobs, min(i_start_jobs+14, n), .false.) res = trim(res)//new_line(' ')//trim(linklist) ! Pagers res = trim(res)//new_line(' ')//"

" if(i_start_jobs /= 1) then write(pager, '(I8)') max(i_start_jobs - 15, 1) res = trim(res)//'<< Newer |' end if if(i_start_jobs+14 < n) then write(pager, '(I8)') i_start_jobs + 15 res = trim(res)//' Older >>' end if res = trim(res)//"

" deallocate(linklist) end if end function generate_jobs_html function request_templated(req) result(resp) use page_template use config, only: template_filepath, project use logging use server_response, only:request, response use http, only: HTTP_CODE_SUCCESS, HTTP_CODE_NOTFOUND implicit none type(request), intent(in)::req type(response)::resp character(1024)::template_file type(template)::page character(64)::first character(len=:), pointer::contents call template_filepath("index.html", template_file) call page%init(trim(template_file)) ! Initialize with success resp%code = HTTP_CODE_SUCCESS call req%path_component(1, first) if(trim(req%location) == "/" .or. trim(req%location) == "/index.html" .or. trim(req%location) == "/home.html") then call page%assign('title', 'Home') else if(trim(req%location) == "/releases.html") then call page%assign('title', 'Releases') contents => generate_releases_html(req) call page%assign('contents', contents) else if(trim(req%location) == "/jobs.html") then call page%assign('title', 'Jobs') contents => generate_jobs_html(req) call page%assign('contents', contents) else if(trim(req%location) == "/players.html") 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.html") then call page%assign('title', 'About') else if(trim(req%location) == "/instructions.html") 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') resp%code = HTTP_CODE_NOTFOUND end if call page%assign('project', project) call page%assign('base_url', req%server) 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/html" end function request_templated subroutine handle_request() use server_response, only:request, response use logging use request_utils use http use iso_fortran_env, only: output_unit use utilities, only: echo_file_stdout implicit none type(request)::req type(response)::resp integer::response_size character(64)::logresponse call build_request_object(req) 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 = request_templated(req) end if ! Perform the response call write_log("Publishing response", LOG_INFO) write(logresponse, *) "Response code is: ", resp%code call write_log(trim(logresponse), LOG_INFO) select case(resp%code) case(HTTP_CODE_REDIRECT) call write_redirect(output_unit, resp%code, trim(resp%url)) case(HTTP_CODE_SUCCESS) inquire(file=resp%body_filename, size=response_size) call write_response_headers(output_unit, resp%code, response_size, trim(resp%body_mimetype)) call echo_file_stdout(resp%body_filename) case(HTTP_CODE_FAILURE) call write_log("Failure reported for location: "//trim(req%location), LOG_NORMAL) ! Need some more... end select call write_log("Cleanup", LOG_INFO) call resp%destroy() call req%destroy() call write_log("Exit handler", LOG_INFO) end subroutine handle_request end module web