aboutsummaryrefslogtreecommitdiff
path: root/request.f90
blob: d470a064e75860eb3d297445cfd39f6334c0d5b1 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
module request
implicit none

    integer, parameter::bufsize = 65536

contains

    function send_string(ssl, str, trimming) result(success)
    use iso_c_binding
    use jessl
    implicit none
    
        logical::success
        type(c_ptr)::ssl
        character(*), intent(in)::str
        logical, intent(in), optional::trimming
        
        integer::start_send
        integer::chars_sent_this_time, chars_sending
        integer::i, bytes
        integer::string_length
        
        character, dimension(bufsize)::buffer
        
        if(present(trimming)) then
            if(trimming) then
                string_length = len_trim(str)
            else
                string_length = len(str)
            end if
        else 
            string_length = len_trim(str)
        end if
        
        success = .true.
        start_send = 1
        do while(start_send <= string_length) 
            
            chars_sending = 0
            do i = start_send, string_length
                buffer(i-start_send+1) = str(i:i) 
                chars_sending = chars_sending + 1
                if(chars_sending == bufsize) then
                    exit
                end if
            end do
            
            ! A null character seems necessary at the end of the request
            if(i >= string_length) then
                chars_sending = chars_sending + 1
                buffer(chars_sending) = c_null_char
            end if
            
            ! Minus 1 because we're sending start_send as well
            chars_sent_this_time = ssl_write(ssl, buffer(start_send:(start_send+chars_sending-1)))
            
            if(chars_sent_this_time < 0) then
                success = .false.
                exit
            end if
            
            start_send = start_send + chars_sent_this_time
            
        end do
        
    end function send_string
    
    function retrieve_characters(ssl, arr) result(chars_read)
    use iso_c_binding
    use jessl
    implicit none
    
        integer::chars_read
        type(c_ptr)::ssl
        character(len=1), dimension(:), intent(inout)::arr

        chars_read = ssl_read(ssl, arr)
        
    end function retrieve_characters
    
end module request