! 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 server_response use iso_c_binding use query_utilities implicit none character(*), parameter::RESPONSE_JSON_OKAY = '{"status": "okay"}' type :: response integer::code ! Used for redirects character(len=:), pointer::url => null() ! Used for inputs in gemini character(len=:), pointer::message => null() logical::temporary_file = .false. character(len=:), pointer::body_filename => null() character(len=64)::body_mimetype character(len=:), pointer::cookiecmd => null() contains procedure :: destroy => response_destroy procedure :: set_message => response_set_message procedure :: set_url => response_set_url procedure :: set_gemini_session_url => reponse_set_gemini_session_url procedure :: set_body_contents => response_temp_file_contents procedure :: set_filename => response_set_filename_using_allocation procedure :: set_cookie_cmd => response_set_cookie_cmd procedure :: set_cookie => response_set_cookie end type type :: request character(len=:), pointer::url => null() character(len=:), pointer::server => null() character(len=:), pointer::protocol => null() character(len=:), pointer::location => null() character(len=:), pointer::page => null() character(len=:), pointer::query_string => null() character(len=:), pointer::token => null() integer::auth_level type(query)::q contains procedure :: init_basics => request_init procedure :: destroy => request_destroy procedure :: last_component => request_last_component procedure :: path_component => request_component procedure :: path_component_int => request_component_int procedure :: path_starting_with_component => request_component_starting_with procedure :: component => request_component_func procedure :: has_query => request_has_query procedure :: is_authenticated_user => request_is_authenticated_user procedure :: set_token => request_set_token procedure :: remove_first_path_component => request_remove_first_path_component procedure :: clear_token => request_clear_token end type request type, extends(request) :: http_request character(len=4)::method = "GET" type(cookies)::c contains procedure :: init => http_request_init procedure :: is_get => request_is_get procedure :: is_post => request_is_post procedure :: clear_token => http_request_clear_token procedure :: destroy => http_request_destroy end type http_request type, extends(request) ::gemini_request contains procedure :: init => gemini_request_init end type gemini_request type, extends(request) :: titan_request integer(kind=8)::size character(len=:), pointer::mimetype type(c_ptr)::ssl_connection contains procedure :: init => titan_request_init procedure :: destroy => titan_request_destroy procedure :: write_to => titan_write_to_filename end type titan_request contains function get_protocol(url) implicit none character(len=*), intent(in)::url character(6)::get_protocol integer::i i = index(url, "://") if(i < 1) then get_protocol = "gemini" else get_protocol = url(1:i-1) end if end function get_protocol function gemini_session_link_url(link, session_token) result(res) implicit none character(*), intent(in)::link character(len=:), pointer, intent(in), optional::session_token character(len=:), pointer::res logical::prepend_session integer::nl nl = len_trim(link) prepend_session = .false. if(link(1:1) == "/") then if(present(session_token)) then if(associated(session_token)) then ! Make sure the url doesn't already have a session token... if(index(link, "/session-"//trim(session_token)) /= 1) then nl = nl + 9 + len_trim(session_token) prepend_session = .true. end if end if end if end if allocate(character(len=nl)::res) if(prepend_session) then res = "/session-"//trim(session_token)//trim(link) else res = link end if end function gemini_session_link_url subroutine request_init(self, fullurl, query_start_char, query_separator) use logging use utilities, only: toupper use captain_db, only: get_session_auth_db use auth_levels, only: AUTH_NONE implicit none class(request) :: self character(*), intent(in)::fullurl character(len=1), intent(in)::query_start_char, query_separator character(len=:), allocatable::temppage integer::i, j, n character(64)::msg n = len_trim(fullurl) allocate(character(len=n) :: self%url) self%url = trim(fullurl) call write_log("URL: "//self%url, LOG_NORMAL) i = index(fullurl, "://") if(i >= 1) then allocate(character(len=(i-1)) :: self%protocol) self%protocol = fullurl(1:i-1) i = i + 3 call write_log("Protocol: "//self%protocol, LOG_DEBUG) else i = 1 end if ! We only want to "assume" the server if a :// was never found j = index(fullurl(i:n), "/") if(j <= 0) then j = len_trim(fullurl) + 1 - i end if allocate(character(len=(j-1)) :: self%server) self%server = fullurl(i:(i+j-1)) i = j+i-1 call write_log("Server: "//self%server//"|", LOG_DEBUG) j = index(fullurl, query_start_char) if(j == 0) then if(n-i+1 == 0) then allocate(character(len=1) :: self%location) self%location = "/" else write(msg, '(I12,1X,I12)') i, n call write_log("i n: "//trim(msg), LOG_DEBUG) allocate(character(len=(n - i + 1)) :: self%location) self%location = fullurl(i:n) end if call write_log("Location: "//self%location, LOG_DEBUG) else allocate(character(len=(n-j)) :: self%query_string) self%query_string = fullurl(j+1:n) allocate(character(len=(j-i)) :: self%location) self%location = fullurl(i:j-1) end if ! and page, which is really just a last location if there is an extension... ! I realize this is not so great, but whatever. allocate(character(len=len(self%location)) :: temppage) call self%last_component(temppage) if(index(temppage, ".") > 0) then allocate(character(len=len_trim(temppage)) :: self%page) self%page = temppage end if deallocate(temppage) if(associated(self%query_string)) then call self%q%init_with_separator(query_separator, self%query_string) if(associated(self%q%get_value("token"))) then self%token => self%q%get_value("token") end if else call self%q%init() end if if(associated(self%token)) then self%auth_level = get_session_auth_db(self%token) else self%auth_level = AUTH_NONE end if end subroutine request_init function request_component_start_location(self, i_component) result(res) implicit none class(request) :: self integer, intent(in)::i_component integer::res integer::i, j, i_last, n res = -1 n = len_trim(self%location) i_last = 0 j = 0 i = index(self%location, "/") do while(i /= i_last .and. j < i_component) j = j + 1 i_last = i i = index(self%location(i_last+1:n), "/") i = i_last + i end do ! Found if(j == i_component) then res = i_last + 1 end if end function request_component_start_location subroutine gemini_request_init(self, str) implicit none class(gemini_request), intent(out)::self character(len=*), intent(in)::str call self%request%init_basics(str, "?", "&") end subroutine gemini_request_init subroutine http_request_init(self, str, server_explicit, protocol_explicit, method, cookiestring) use captain_db, only: get_session_auth_db use auth_levels, only: AUTH_NONE use utilities, only: toupper implicit none class(http_request), intent(out)::self character(len=*), intent(in)::str character(*), intent(in), optional::server_explicit, protocol_explicit, method, cookiestring character(len=1024)::fullurl, passurl fullurl = " " if(present(server_explicit)) then if(index(str, server_explicit) == 1) then passurl = str(len_trim(server_explicit)+1:len_trim(str)) else passurl = str end if else passurl = str end if call self%request%init_basics(passurl, "?", "&") allocate(character(len=4)::self%protocol) self%protocol = "http" if(present(server_explicit)) then allocate(character(len=len_trim(server_explicit)) :: self%server) self%server = server_explicit end if if(present(method)) then self%method = method call toupper(self%method) else self%method = "GET" end if if(present(cookiestring)) then call self%c%init(cookiestring) if(.not.associated(self%token) .and. associated(self%c%get_value("token"))) then self%token => self%c%get_value("token") end if else call self%c%init() end if if(associated(self%token)) then self%auth_level = get_session_auth_db(self%token) else self%auth_level = AUTH_NONE end if end subroutine http_request_init function request_is_authenticated_user(self) use captain_db implicit none class(request), intent(in)::self logical::request_is_authenticated_user request_is_authenticated_user = .false. if(associated(self%token)) then request_is_authenticated_user = is_valid_session_db(self%token) if(request_is_authenticated_user) then call update_session_db(self%token) end if end if end function request_is_authenticated_user subroutine request_component(self, i_component, res) use logging implicit none class(request) :: self integer, intent(in)::i_component character(*), intent(out)::res integer::i, j, i_last, n res = " " n = len_trim(self%location) i_last = 0 j = 0 i = index(self%location, "/") do while(i /= i_last .and. j < i_component) j = j + 1 i_last = i i = index(self%location(i_last+1:n), "/") i = i_last + i end do ! Found if(j == i_component) then if(i == i_last) then res = self%location(i_last+1:n) else res = self%location(i_last+1:i-1) end if end if end subroutine request_component subroutine request_component_starting_with(self, i_component, res) implicit none class(request) :: self integer, intent(in)::i_component character(*), intent(out)::res integer::string_index_component string_index_component = request_component_start_location(self, i_component) if(string_index_component > 0) then res = self%location(string_index_component:len_trim(self%location)) else res = " " end if end subroutine request_component_starting_with function request_component_int(self, i) result(res) implicit none class(request) :: self integer, intent(in)::i integer :: res character(24)::restext restext = " " call self%path_component(i, restext) read(restext, '(I16)') res end function request_component_int function request_component_func(self, i) result(res) implicit none class(request) :: self integer, intent(in)::i character(128) :: res res = " " call self%path_component(i, res) end function request_component_func subroutine request_last_component(self, res) implicit none class(request) :: self character(*), intent(out)::res integer::i, n n = len_trim(self%location) if(n == 1) then res = "/" else i = index(self%location, "/", back=.true.) if(i == n) then i = index(self%location(1:n-1), "/", back=.true.) if(i > 0) then res = self%location(i+1:n-1) else res = "/" end if else res = self%location((i+1):n) end if end if end subroutine request_last_component function request_is_get(self) result(res) implicit none class(http_request)::self logical::res res = (self%method == "GET") end function request_is_get function request_is_post(self) result(res) implicit none class(http_request)::self logical::res res = (self%method == "POST") end function request_is_post function request_has_query(self) implicit none class(request)::self logical::request_has_query request_has_query = associated(self%query_string) .and. self%q%component_count() > 0 end function request_has_query subroutine request_set_token(self, token) use captain_db implicit none class(request), intent(inout)::self character(len=*), intent(in)::token allocate(character(len=len_trim(token)) :: self%token) self%token = token self%auth_level = get_session_auth_db(self%token) end subroutine request_set_token subroutine request_clear_token(self) implicit none class(request), intent(inout)::self self%token => null() self%auth_level = 0 end subroutine request_clear_token subroutine http_request_clear_token(self) implicit none class(http_request), intent(inout)::self self%token => null() self%auth_level = 0 end subroutine http_request_clear_token ! This routine is needed if we're stripping session identifiers ! in Gemini URLs subroutine request_remove_first_path_component(self) implicit none class(request), intent(inout)::self character(len=:), pointer::newloc integer::i, j, n i = 1 if(self%location(1:1) == "/") then i = i + 1 end if n = len_trim(self%location) j = index(self%location(i:n), "/") + (i-1) if(j == 0) then j = n end if ! First component should be self%location(i:j) n = n - (j-i+1) allocate(character(len=n)::newloc) if(i > 1) then newloc(1:1) = self%location(1:1) end if newloc(2:n) = self%location(j+1:len_trim(self%location)) deallocate(self%location) self%location => newloc newloc => null() end subroutine request_remove_first_path_component subroutine request_destroy(self) implicit none class(request) :: self if(associated(self%url)) then deallocate(self%url) end if if(associated(self%server)) then deallocate(self%server) end if if(associated(self%location)) then deallocate(self%location) end if if(associated(self%query_string)) then deallocate(self%query_string) end if if(associated(self%protocol)) then deallocate(self%protocol) end if if(associated(self%page)) then deallocate(self%page) end if ! Needs to happen before we destroy the cookies and query string call self%clear_token() call self%q%destroy() end subroutine request_destroy subroutine http_request_destroy(self) implicit none class(http_request) :: self call self%request%destroy() call self%c%destroy() end subroutine http_request_destroy subroutine response_destroy(resp) use utilities, only: delete_file implicit none class(response)::resp if(associated(resp%url)) then deallocate(resp%url) end if if(associated(resp%message)) then deallocate(resp%message) end if if(associated(resp%body_filename)) then if(resp%temporary_file) then call delete_file(resp%body_filename) end if deallocate(resp%body_filename) end if if(associated(resp%cookiecmd)) then deallocate(resp%cookiecmd) end if end subroutine response_destroy subroutine response_set_cookie_cmd(resp, str) implicit none class(response)::resp character(*), intent(in)::str integer::newlength character(len=:), pointer::tmp if(len_trim(str) > 0) then if(associated(resp%cookiecmd)) then newlength = len(resp%cookiecmd)+len_trim(str)+1 allocate(character(len=newlength)::tmp) tmp = resp%cookiecmd//new_line(' ')//trim(str) deallocate(resp%cookiecmd) resp%cookiecmd => tmp tmp => null() else allocate(character(len=len_trim(str)) :: resp%cookiecmd) resp%cookiecmd = trim(str) end if end if end subroutine response_set_cookie_cmd subroutine response_set_cookie(resp, k, v, httponly) implicit none class(response)::resp character(len=*), intent(in)::k, v logical, optional::httponly character(len=10)::httponly_trailing httponly_trailing = "; HttpOnly" if(present(httponly)) then if(.not. httponly) then httponly_trailing = " " end if end if call resp%set_cookie_cmd("Set-Cookie: "//trim(k)//"="//trim(v)//"; SameSite=Strict"//trim(httponly_trailing)) end subroutine response_set_cookie subroutine response_set_message(resp, str) implicit none class(response)::resp character(*), intent(in)::str if(len_trim(str) > 0) then allocate(character(len=len_trim(str)) :: resp%message) resp%message = trim(str) end if end subroutine response_set_message subroutine response_set_url(resp, str) implicit none class(response)::resp character(*), intent(in), optional::str if(associated(resp%url)) then deallocate(resp%url) resp%url => null() end if if(present(str)) then if(len_trim(str) > 0) then allocate(character(len=len_trim(str)) :: resp%url) resp%url = trim(str) end if end if end subroutine response_set_url subroutine reponse_set_gemini_session_url(resp, str, session_token) !use request_utils, only: gemini_session_link_url implicit none class(response), intent(inout)::resp character(*), intent(in)::str character(len=:), pointer, intent(in)::session_token character(len=:), pointer::session_url if(associated(session_token)) then session_url => gemini_session_link_url(str, session_token) call resp%set_url(session_url) deallocate(session_url) else call resp%set_url(str) end if end subroutine reponse_set_gemini_session_url subroutine response_temp_file_contents(resp, str, mimetype) use utilities, only: generate_temporary_filename implicit none class(response)::resp character(*), intent(in)::str character(*), intent(in), optional::mimetype integer::unum resp%body_filename => generate_temporary_filename() open(newunit=unum, file=resp%body_filename, action="write", status="new") write(unum, *) str close(unum) resp%temporary_file = .true. if(present(mimetype)) then resp%body_mimetype = mimetype else resp%body_mimetype = "text/plain" end if end subroutine response_temp_file_contents subroutine response_set_filename_using_allocation(resp, fname, mimetype) implicit none class(response)::resp character(*), intent(in)::fname character(*), intent(in), optional::mimetype allocate(character(len=len_trim(fname)) :: resp%body_filename) resp%body_filename = trim(fname) if(present(mimetype)) then resp%body_mimetype = mimetype else resp%body_mimetype = "text/plain" end if end subroutine response_set_filename_using_allocation subroutine titan_request_init(self, str, ssl_connection) use logging implicit none class(titan_request)::self character(len=*), intent(in)::str type(c_ptr)::ssl_connection character(len=:), pointer::size_text integer::ierr call self%request%init_basics(str, ";", ";") size_text => self%q%get_value("size") if(associated(size_text)) then read(size_text, '(I16)', iostat=ierr) self%size if(ierr /= 0) then self%size = 0 end if end if self%mimetype => self%q%get_value("mime") self%token => self%q%get_value("token") self%ssl_connection = ssl_connection end subroutine titan_request_init subroutine titan_request_destroy(self) implicit none class(titan_request)::self self%token => null() call request_destroy(self) end subroutine titan_request_destroy function titan_write_to_filename(self, filename) result(success) use jessl, only: ssl_read use logging implicit none class(titan_request)::self character(*), intent(in)::filename integer::unum character(len=1), dimension(1024)::buf integer::bufread integer(kind=8)::bytes_to_go integer::istat logical::success, file_exists !character(128)::msg success = .false. ! Writing to an existing file has been broken for some reason... inquire(file=filename, exist=file_exists) if(file_exists) then ! GNU Extension, boo... call unlink(filename) end if open(newunit=unum, file=filename, status="unknown", & action="write", access='stream', iostat=istat) bytes_to_go = self%size do while(bytes_to_go > 0 .and. istat == 0) bufread = ssl_read(self%ssl_connection, buf) bytes_to_go = bytes_to_go - bufread write(unum, iostat=istat) buf(1:bufread) end do close(unum) success = (istat == 0) end function titan_write_to_filename end module server_response