aboutsummaryrefslogtreecommitdiff
path: root/captain/response.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-04-02 16:37:36 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-04-02 16:37:36 -0400
commitbff06af2176e2f2813482b4fa7b4096a9982999b (patch)
treeb84a25c66487355ce4b1bb123f6fc01b2992ef46 /captain/response.f90
parentb27bd7cfa58eb82fc2a6c76aaa848e07a6fa7c24 (diff)
downloadlevitating-bff06af2176e2f2813482b4fa7b4096a9982999b.tar.gz
levitating-bff06af2176e2f2813482b4fa7b4096a9982999b.zip
More work on titan request handling, including a titan request derived type
Diffstat (limited to 'captain/response.f90')
-rw-r--r--captain/response.f9090
1 files changed, 90 insertions, 0 deletions
diff --git a/captain/response.f90 b/captain/response.f90
index 2f48caa..cd1895a 100644
--- a/captain/response.f90
+++ b/captain/response.f90
@@ -47,6 +47,19 @@ module server_response
end type request
+ type, extends(request) :: titan_request
+
+ integer(kind=8)::size
+ character(len=:), pointer::mimetype
+ character(len=:), pointer::token
+
+ contains
+
+ procedure :: init_from_request => titan_request_init
+ procedure :: destroy => titan_request_destroy
+
+ end type titan_request
+
contains
subroutine request_init(self, str)
@@ -300,4 +313,81 @@ contains
end subroutine response_set_filename_using_allocation
+ function titan_get_request_value( full_location, label) result(p)
+ implicit none
+
+ character(*), intent(in)::full_location, label
+ character(len=:), pointer::p
+
+ integer::i, j, n, label_width
+
+ label_width = len_trim(label)
+
+ n = len_trim(full_location)
+ i = index(full_location, ";"//trim(label)//"=")
+ j = index(full_location(i+1:n), ";")
+ if(j<=0) then
+ j = n
+ else
+ j = j+i
+ end if
+ i = i + label_width + 2
+
+ allocate(character(len=(j-i+1))::p)
+ p = full_location(i:j)
+
+ end function titan_get_request_value
+
+ subroutine titan_request_init(self, regular_request)
+ implicit none
+
+ class(titan_request)::self
+ class(request), intent(inout)::regular_request
+
+ character(len=:), pointer::size_text
+ integer::i, ierr
+
+ self%url => regular_request%url
+ regular_request%url => null()
+
+ self%protocol => regular_request%protocol
+ regular_request%protocol => null()
+
+ self%server => regular_request%server
+ regular_request%server => null()
+
+ self%query_string => regular_request%query_string
+
+ i = index(regular_request%location, ";")
+ allocate(character(len=(i-1)) :: self%location)
+ self%location = regular_request%location(1:i-1)
+
+ size_text => titan_get_request_value(regular_request%location, "size")
+ read(size_text, *, iostat=ierr) self%size
+ if(ierr <= 0) then
+ self%size = 0
+ end if
+ deallocate(size_text)
+
+ self%mimetype => titan_get_request_value(regular_request%location, "mime")
+ self%token => titan_get_request_value(regular_request%location, "token")
+
+ end subroutine titan_request_init
+
+ subroutine titan_request_destroy(self)
+ implicit none
+
+ class(titan_request)::self
+
+ if(associated(self%mimetype)) then
+ deallocate(self%mimetype)
+ end if
+ if(associated(self%token)) then
+ deallocate(self%token)
+ end if
+
+ call request_destroy(self)
+
+ end subroutine titan_request_destroy
+
end module server_response