aboutsummaryrefslogtreecommitdiff
path: root/captain/response.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 11:47:53 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-05-06 11:47:53 -0400
commit13a08c508005b9c3b280c05459e943a268b5ccc5 (patch)
tree246029b796ea10d7da11b7032970501bfa605589 /captain/response.f90
parentb9cac9bb26fe388abff34fa4fc562b0804cabb2e (diff)
downloadlevitating-13a08c508005b9c3b280c05459e943a268b5ccc5.tar.gz
levitating-13a08c508005b9c3b280c05459e943a268b5ccc5.zip
Fixed static file handler to allow subdirectories properly. Fixed directory file listing under Linux. Release listing now works through CGI.
Diffstat (limited to 'captain/response.f90')
-rw-r--r--captain/response.f9050
1 files changed, 50 insertions, 0 deletions
diff --git a/captain/response.f90 b/captain/response.f90
index 3982f1e..a4fe24e 100644
--- a/captain/response.f90
+++ b/captain/response.f90
@@ -70,6 +70,7 @@ implicit none
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
end type request
@@ -169,6 +170,37 @@ contains
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 request_component(self, i_component, res)
use logging
implicit none
@@ -205,6 +237,24 @@ contains
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