aboutsummaryrefslogtreecommitdiff
path: root/common/request.f90
diff options
context:
space:
mode:
Diffstat (limited to 'common/request.f90')
-rw-r--r--common/request.f9012
1 files changed, 9 insertions, 3 deletions
diff --git a/common/request.f90 b/common/request.f90
index d7b3120..fe4d970 100644
--- a/common/request.f90
+++ b/common/request.f90
@@ -218,7 +218,7 @@ contains
end subroutine get_server_from_url
- function send_string(ssl, str, trimming) result(success)
+ function send_string(ssl, str, trimming, allow_trailing_null) result(success)
use iso_c_binding
use jessl
implicit none
@@ -226,12 +226,13 @@ contains
logical::success
type(c_ptr)::ssl
character(*), intent(in)::str
- logical, intent(in), optional::trimming
+ logical, intent(in), optional::trimming, allow_trailing_null
integer::start_send
integer::chars_sent_this_time, chars_sending
integer::i
integer::string_length
+ logical::end_with_null
character, dimension(bufsize)::buffer
@@ -245,6 +246,11 @@ contains
string_length = len_trim(str)
end if
+ end_with_null = .true.
+ if(present(allow_trailing_null)) then
+ end_with_null = allow_trailing_null
+ end if
+
success = .true.
start_send = 1
do while(start_send <= string_length)
@@ -259,7 +265,7 @@ contains
end do
! A null character seems necessary at the end of the request
- if(i >= string_length) then
+ if(i >= string_length .and. end_with_null) then
chars_sending = chars_sending + 1
buffer(chars_sending) = c_null_char
end if