aboutsummaryrefslogtreecommitdiff
path: root/common/jessl.f90
diff options
context:
space:
mode:
Diffstat (limited to 'common/jessl.f90')
-rw-r--r--common/jessl.f9022
1 files changed, 21 insertions, 1 deletions
diff --git a/common/jessl.f90 b/common/jessl.f90
index 5ad90fd..1974082 100644
--- a/common/jessl.f90
+++ b/common/jessl.f90
@@ -203,19 +203,39 @@ implicit none
contains
- function ssl_read(ssl, buf)
+ ! The timeout is specified in milliseconds, fyi
+ function ssl_read(ssl, buf, timeout)
use iso_c_binding
+ use utilities, only: sleep_ms
implicit none
type(c_ptr)::ssl
character(len=1), dimension(:), intent(out)::buf
+ integer, intent(in), optional::timeout
integer::ssl_read
integer::bufsize
+ integer(kind=8)::start_time, current_time, count_rate, dt
+
character(kind=c_char), dimension(:), allocatable::cbuf
bufsize = size(buf)
allocate(cbuf(bufsize))
+ if(present(timeout)) then
+
+ call system_clock(start_time, count_rate=count_rate)
+ current_time = start_time
+
+ dt = 0
+
+ do while(ssl_pending(ssl) <= 0 .and. dt < timeout .and. dt >= 0)
+ call sleep_ms(timeout / 10)
+ call system_clock(current_time)
+ dt = ((current_time - start_time)*1000)/count_rate
+ end do
+
+ end if
+
ssl_read = read_c(ssl, cbuf, bufsize)
buf = cbuf