aboutsummaryrefslogtreecommitdiff
path: root/protocol.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2020-05-05 07:54:53 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2020-05-05 07:54:53 -0400
commit723324ae71f8209e4b1757a3f84bd0e66b6c6319 (patch)
tree91737e20dba6e06068ea37bb9bcb79122a12d427 /protocol.f90
parent1ef40339cc161484b3e70d34ab4d507b758b29eb (diff)
downloadLR-87-723324ae71f8209e4b1757a3f84bd0e66b6c6319.tar.gz
LR-87-723324ae71f8209e4b1757a3f84bd0e66b6c6319.zip
Actual client can now load and display a page using dumb_renderer
Diffstat (limited to 'protocol.f90')
-rw-r--r--protocol.f9043
1 files changed, 40 insertions, 3 deletions
diff --git a/protocol.f90 b/protocol.f90
index bd109c1..52b6430 100644
--- a/protocol.f90
+++ b/protocol.f90
@@ -16,6 +16,7 @@ contains
function request_url(url, unit_number, server_name) result(returncode)
use request
use iso_c_binding
+ use file_handling, only: mark_file_end
implicit none
character(*), intent(in)::url
@@ -47,7 +48,7 @@ contains
if(send_string(conn%ssl, url//c_carriage_return//c_new_line, trimming=.false.)) then
bytes_received = retrieve_characters(conn%ssl, buffer)
-
+ Print *, bytes_received
do while(bytes_received > 0)
do i=1, bytes_received
@@ -57,6 +58,8 @@ contains
bytes_received = retrieve_characters(conn%ssl, buffer)
end do
+ call mark_file_end(unit_number)
+
rewind(unit_number)
read(unit_number, '(I1)') returncode
@@ -64,18 +67,52 @@ contains
returncode = -1
write(unit_number, *) "Send Error: Could Not Send Request"
-
+ write(*, *) "Send Error: Could Not Send Request"
end if
else
returncode = -1
write(unit_number, *) "Connection Error: "//trim(translate_connection_code(conn%code))
-
+ write(*, *) "Connection Error: "//trim(translate_connection_code(conn%code))
end if
call close_connection(conn)
end function request_url
+ subroutine get_redirect_url(unit_number, url)
+ implicit none
+
+ integer, intent(in)::unit_number
+ character(*), intent(inout)::url
+
+ character::search
+ integer::i, istat
+
+ rewind(unit_number)
+
+ ! Status code
+ read(unit_number, '(A1)', advance='no') search
+ read(unit_number, '(A1)', advance='no') search
+
+ ! Clear the url
+ url = repeat(" ", len(url))
+
+ ! At least one whitespace, but whatever...
+ read(unit_number, '(A1)', advance='no') search
+ do while(search == " " .or. search == CHAR(9))
+ read(unit_number, '(A1)', advance='no', iostat=istat) search
+ end do
+
+ ! Now search contains our first url component
+ i = 0
+ do while(search /= CHAR(13) .and. i < len(url) .and. istat == 0)
+ i = i + 1
+ url(i:i) = search
+ read(unit_number, '(A1)', advance='no', iostat=istat) search
+ end do
+
+ end subroutine get_redirect_url
+
end module gemini_protocol \ No newline at end of file