aboutsummaryrefslogtreecommitdiff
path: root/captain/response.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/response.f90')
-rw-r--r--captain/response.f9058
1 files changed, 35 insertions, 23 deletions
diff --git a/captain/response.f90 b/captain/response.f90
index a82f53d..49f735e 100644
--- a/captain/response.f90
+++ b/captain/response.f90
@@ -199,10 +199,14 @@ contains
call write_log("URL: "//self%url, LOG_NORMAL)
i = index(fullurl, "://")
- allocate(character(len=(i-1)) :: self%protocol)
- self%protocol = fullurl(1:i-1)
- i = i + 3
- call write_log("Protocol: "//self%protocol, LOG_DEBUG)
+ 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), "/")
@@ -228,15 +232,10 @@ contains
self%location = fullurl(i:n)
end if
call write_log("Location: "//self%location, LOG_DEBUG)
-
- call self%q%init()
-
else
allocate(character(len=(n-j)) :: self%query_string)
self%query_string = fullurl(j+1:n)
- call self%q%init_with_separator(query_separator, self%query_string)
-
allocate(character(len=(j-i)) :: self%location)
self%location = fullurl(i:j-1)
end if
@@ -252,7 +251,7 @@ contains
deallocate(temppage)
if(associated(self%query_string)) then
- call self%q%init(self%query_string)
+ 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")
@@ -313,23 +312,36 @@ contains
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
+ character(len=1024)::fullurl, passurl
fullurl = " "
- if(present(protocol_explicit) .and. present(server_explicit)) then
- fullurl = trim(protocol_explicit)//"://"//trim(server_explicit)//trim(str)
+ 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
- fullurl = trim(str)
+ passurl = str
end if
+
+ call self%request%init_basics(passurl, "?", "&")
- call self%request%init_basics(fullurl, "?", "&")
+ 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
@@ -535,7 +547,6 @@ contains
implicit none
class(request), intent(inout)::self
- logical::safe_to_deallocate
self%token => null()
self%auth_level = 0
@@ -559,7 +570,7 @@ contains
implicit none
class(request), intent(inout)::self
- character(len=:), pointer::first, newloc
+ character(len=:), pointer::newloc
integer::i, j, n
@@ -797,6 +808,7 @@ contains
end subroutine response_set_filename_using_allocation
subroutine titan_request_init(self, str, ssl_connection)
+ use logging
implicit none
class(titan_request)::self
@@ -804,18 +816,18 @@ contains
type(c_ptr)::ssl_connection
character(len=:), pointer::size_text
- integer::i, ierr
+ integer::ierr
call self%request%init_basics(str, ";", ";")
size_text => self%q%get_value("size")
- read(size_text, '(I16)', iostat=ierr) self%size
- if(ierr /= 0) then
- self%size = 0
+ if(associated(size_text)) then
+ read(size_text, '(I16)', iostat=ierr) self%size
+ if(ierr /= 0) then
+ self%size = 0
+ end if
end if
- deallocate(size_text)
-
self%mimetype => self%q%get_value("mime")
self%token => self%q%get_value("token")