module server_response integer, parameter::GEMINI_CODE_INPUT = 10 integer, parameter::GEMINI_CODE_SUCCESS = 20 integer, parameter::GEMINI_CODE_REDIRECT = 30 integer, parameter::GEMINI_CODE_PERMFAIL = 50 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 contains procedure :: destroy => response_destroy procedure :: set_message => response_set_message procedure :: set_url => response_set_url 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::query_string => null() contains procedure :: init => request_init procedure :: destroy => request_destroy procedure :: last_component => request_last_component procedure :: path_component => request_component end type request contains subroutine request_init(self, str) use logging implicit none class(request) :: self character(*), intent(in)::str integer::i, j, n n = len_trim(str) allocate(character(len=n) :: self%url) self%url = trim(str) call write_log("URL: "//self%url) i = index(str, "://") allocate(character(len=(i-1)) :: self%protocol) self%protocol = str(1:i-1) call write_log("Protocol: "//self%protocol) i = i + 3 j = index(str(i:n), "/") if(j <= 0) then j = len_trim(str) + 1 - i end if allocate(character(len=(j-1)) :: self%server) self%server = str(i:(i+j-1)) call write_log("Server: "//self%server//"|") i = j+i-1 j = index(str, "?") if(j == 0) then if(n-i+1 == 0) then allocate(character(len=1) :: self%location) self%location = "/" else allocate(character(len=(n - i + 1)) :: self%location) self%location = str(i:n) end if call write_log("Location: "//self%location) else allocate(character(len=(n-j)) :: self%query_string) self%query_string = str(j+1:n) call write_log("Query: "//self%query_string) allocate(character(len=(j-i)) :: self%location) self%location = str(i:j-1) call write_log("Location: "//self%location) end if end subroutine request_init 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 call write_log("RC: "//self%location(i:n)) 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) call write_log("Last! "//trim(res)) else res = self%location(i_last+1:i-1) end if end if end subroutine request_component 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 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 end subroutine request_destroy subroutine response_destroy(resp) 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 unlink(resp%body_filename) end if deallocate(resp%body_filename) end if end subroutine response_destroy 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)::str if(len_trim(str) > 0) then allocate(character(len=len_trim(str)) :: resp%url) resp%url = trim(str) end if end subroutine response_set_url end module server_response