aboutsummaryrefslogtreecommitdiff
path: root/files.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 /files.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 'files.f90')
-rw-r--r--files.f9032
1 files changed, 25 insertions, 7 deletions
diff --git a/files.f90 b/files.f90
index 45bc116..cbdb44d 100644
--- a/files.f90
+++ b/files.f90
@@ -3,8 +3,29 @@ module file_handling
integer, parameter::file_type_plain_text = 1
integer, parameter::file_type_gemini = 2
+ character(17), parameter::end_indicator = "** END OF FILE **"
+
contains
+ subroutine mark_file_end(unit_number)
+ implicit none
+
+ integer, intent(in)::unit_number
+
+ Write(unit_number, '(A17)') end_indicator
+
+ end subroutine mark_file_end
+
+ function is_file_end_marker(text)
+ implicit none
+
+ character(*), intent(in)::text
+ logical::is_file_end_marker
+
+ is_file_end_marker = (index(text, end_indicator) > 0)
+
+ end function is_file_end_marker
+
function read_line_text(unit_number, iostatus) result(res)
implicit none
@@ -24,7 +45,7 @@ contains
end do
length = (endpos - startpos + 1)
- print '(A10, I8)', "allocated", length
+ !print '(A10, I8)', "allocated", length
allocate(character(len=length) :: res)
res = repeat(' ', length)
@@ -97,7 +118,6 @@ contains
type(line), pointer::first_line
type(line), pointer::walker, next_line
- character::c
integer::iostatus
logical::preformatted_on
@@ -110,9 +130,9 @@ contains
walker=>first_line
- call process_line(walker, file_type, preformatted_on)
-
- do while(iostatus /= -1) ! -1 should be end of file
+ do while(iostatus /= -1 .and. .not. is_file_end_marker(walker%text)) ! -1 should be end of file
+
+ call process_line(walker, file_type, preformatted_on)
allocate(next_line)
next_line%next => null()
@@ -122,8 +142,6 @@ contains
walker => walker%next
walker%text = read_line_text(unit_number, iostatus)
- print *, walker%text
- call process_line(walker, file_type, preformatted_on)
end do