aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f9039
1 files changed, 28 insertions, 11 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index 0bd21ee..3b94379 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -70,7 +70,7 @@ contains
use config
implicit none
- type(request), intent(in)::req
+ class(request), intent(in)::req
type(template), intent(inout)::page
character(len=128)::username
@@ -93,20 +93,27 @@ contains
end subroutine handle_basic_template_components
subroutine build_request_object(req)
- use server_response, only:request
+ use server_response, only:http_request
use logging
implicit none
- type(request), intent(out)::req
- character(len=:), allocatable::url, script_name, cookie
+ type(http_request), intent(out)::req
+ character(len=:), allocatable::url, script_name, cookie, server_name, fullurl
character(len=4)::method
- integer::url_size, cookie_size
+ integer::url_size, cookie_size, sn_size
call get_environment_variable("REQUEST_URI", length=url_size)
- allocate(character(len=url_size)::url, script_name)
+ allocate(character(len=url_size)::url)
call get_environment_variable("REQUEST_URI", url)
+
+ call get_environment_variable("SCRIPT_NAME", length=sn_size)
+ allocate(character(len=sn_size)::script_name)
call get_environment_variable("SCRIPT_NAME", script_name)
+ call get_environment_variable("SERVER_NAME", length=sn_size)
+ allocate(character(len=sn_size)::server_name)
+ call get_environment_variable("SERVER_NAME", server_name)
+
call get_environment_variable("REQUEST_METHOD", method)
call get_environment_variable("HTTP_COOKIE", length=cookie_size)
@@ -117,6 +124,15 @@ contains
end if
! If we're in CGI mode, treat the "server" as the script name
+ call write_log("URL IS "//trim(url), level=LOG_DEBUG)
+ call write_log("SE IS "//trim(script_name), level=LOG_DEBUG)
+
+ ! We don't actually use this fabircated URL, but it is helpful for debugging
+ ! whatever the hell is going on when the request object is built...
+ allocate(character(len=(len_trim(server_name) + len_trim(url) + 7)) :: fullurl)
+ fullurl = "http://"//trim(server_name)//trim(url)
+ call write_log("FULL URL WOULD BE "//trim(fullurl), level=LOG_DEBUG)
+
if(allocated(cookie)) then
call req%init(url, server_explicit=script_name, protocol_explicit="http", method=method, cookiestring=cookie)
deallocate(cookie)
@@ -126,6 +142,7 @@ contains
deallocate(url)
deallocate(script_name)
+ deallocate(server_name)
end subroutine build_request_object
@@ -1025,7 +1042,7 @@ contains
use utilities, only: build_date
implicit none
- type(request), intent(in)::req
+ class(request), intent(in)::req
type(response)::resp
character(64)::template_to_use
@@ -1218,13 +1235,13 @@ contains
use page_template
use config, only: template_filepath, global_permissions
use logging
- use server_response, only:request, response
+ use server_response, only:http_request, response
use http_post_utilities
use query_utilities, only: query
use http_codes
implicit none
- type(request), intent(in)::req
+ type(http_request), intent(in)::req
type(response)::resp
type(query)::posted
@@ -1305,7 +1322,7 @@ contains
end function handle_post
subroutine handle_request()
- use server_response, only:request, response
+ use server_response, only:http_request, response
use logging
use request_utils
use http_codes
@@ -1314,7 +1331,7 @@ contains
use utilities, only: echo_file_stdout
implicit none
- type(request)::req
+ type(http_request)::req
type(response)::resp
integer::response_size