aboutsummaryrefslogtreecommitdiff
path: root/captain/response.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/response.f90')
-rw-r--r--captain/response.f9037
1 files changed, 30 insertions, 7 deletions
diff --git a/captain/response.f90 b/captain/response.f90
index 2659c31..3933eb8 100644
--- a/captain/response.f90
+++ b/captain/response.f90
@@ -22,13 +22,15 @@
module server_response
use iso_c_binding
+use query_utilities
implicit none
- integer, parameter::GEMINI_CODE_INPUT = 10
- integer, parameter::GEMINI_CODE_SUCCESS = 20
- integer, parameter::GEMINI_CODE_REDIRECT = 30
- integer, parameter::GEMINI_CODE_TEMPFAIL = 40
- integer, parameter::GEMINI_CODE_PERMFAIL = 50
+ integer, parameter::GEMINI_CODE_INPUT = 10
+ integer, parameter::GEMINI_CODE_SUCCESS = 20
+ integer, parameter::GEMINI_CODE_REDIRECT = 30
+ integer, parameter::GEMINI_CODE_TEMPFAIL = 40
+ integer, parameter::GEMINI_CODE_PERMFAIL = 50
+ integer, parameter::GEMINI_CODE_BAD_REQUEST = 59
character(*), parameter::RESPONSE_JSON_OKAY = '{"status": "okay"}'
@@ -64,7 +66,10 @@ implicit none
character(len=:), pointer::location => null()
character(len=:), pointer::page => null()
character(len=:), pointer::query_string => null()
+ character(len=:), pointer::token => null()
character(len=4)::method = "GET"
+
+ type(query)::q
contains
@@ -77,14 +82,14 @@ implicit none
procedure :: component => request_component_func
procedure :: is_get => request_is_get
procedure :: is_post => request_is_post
-
+ procedure :: has_query => request_has_query
+
end type request
type, extends(request) :: titan_request
integer(kind=8)::size
character(len=:), pointer::mimetype
- character(len=:), pointer::token
type(c_ptr)::ssl_connection
@@ -197,6 +202,12 @@ contains
call toupper(self%method)
end if
+ if(associated(self%query_string)) then
+ call self%q%init(self%query_string)
+ else
+ call self%q%init()
+ end if
+
end subroutine request_init
function request_component_start_location(self, i_component) result(res)
@@ -365,6 +376,16 @@ contains
end function request_is_post
+ function request_has_query(self)
+ implicit none
+
+ class(request)::self
+ logical::request_has_query
+
+ request_has_query = associated(self%query_string) .and. self%q%component_count() > 0
+
+ end function request_has_query
+
subroutine request_destroy(self)
implicit none
@@ -394,6 +415,8 @@ contains
deallocate(self%page)
end if
+ call self%q%destroy()
+
end subroutine request_destroy
subroutine response_destroy(resp)