aboutsummaryrefslogtreecommitdiff
path: root/render.f90
diff options
context:
space:
mode:
Diffstat (limited to 'render.f90')
-rw-r--r--render.f90159
1 files changed, 83 insertions, 76 deletions
diff --git a/render.f90 b/render.f90
index 3cbb2bc..74b1406 100644
--- a/render.f90
+++ b/render.f90
@@ -306,45 +306,51 @@ contains
end if
endpos = len_trim(text)
+
w = width_of_line(r, text, my_start, endpos, proportional_type)
if(w > r%max_width) then
w = 0
endpos = startpos+1
- do while(w <= r%max_width)
+ do while(w <= r%max_width .and. endpos < len_trim(text))
last_end = endpos
endpos = endpos + 1
- do while(text(endpos:endpos) /= ' ' .and. text(endpos:endpos) /= '-')
+ do while(text(endpos:endpos) /= ' ' .and. text(endpos:endpos) /= '-' .and. endpos < len_trim(text))
endpos = endpos + 1
end do
- w = width_of_line(r, text, my_start, endpos, proportional_type)
+ if(my_start < endpos) then
+ w = width_of_line(r, text, my_start, endpos, proportional_type)
+ else
+ w = 0
+ exit
+ end if
end do
-
+
endpos = last_end
-
+
end if
-
+
end function wrap_line
-
+
function get_start_position_and_type(text, proportional_type) result(startpos)
implicit none
-
+
character(*), intent(in)::text
integer, intent(out)::proportional_type
integer::startpos
-
+
startpos = 1
proportional_type = proportional_type_normal
-
+
! Check for headings first
- do while(text(startpos:startpos) == '#')
+ do while(text(startpos:startpos) == '#')
proportional_type = proportional_type + 1
startpos = startpos + 1
end do
-
+
if(proportional_type == proportional_type_normal) then
if(text(1:1) == '*') then
proportional_type = proportional_type_list_item
@@ -361,113 +367,114 @@ contains
startpos = startpos + 1
end do
end if
-
+
end function get_start_position_and_type
-
+
function calculate_wrapping(r, text) result(breaks)
implicit none
-
+
class(renderer)::r
character(*), intent(in)::text
integer, dimension(:), pointer::breaks
-
+
integer::startpos, endpos
integer::proportional_type
logical::list_item, quotation
-
+
integer::current_allocation
integer::break_count
integer, dimension(:), pointer::realloc
-
+
current_allocation = 16
break_count = 0
allocate(breaks(current_allocation))
if(len_trim(text) > 0) then
-
+
startpos = get_start_position_and_type(text, proportional_type)
-
+
endpos = wrap_line(r, text, startpos, proportional_type)
do while(endpos > startpos)
-
+
! Save this break
break_count = break_count + 1
-
+
! Messy memory handling...
if(break_count > current_allocation) then
realloc => breaks
breaks => null()
-
+
allocate(breaks(current_allocation + 16))
breaks(1:current_allocation) = realloc
current_allocation = current_allocation + 16
deallocate(realloc)
end if
-
+
! Now actually save it
breaks(break_count) = endpos
-
+
! Advance string positions
startpos = endpos+1
do while(text(startpos:startpos) == ' ')
startpos = startpos + 1
end do
-
+
! Do not mark as a list item for subsequent lines
if(proportional_type == proportional_type_list_item) then
proportional_type = proportional_type_normal
end if
-
+
endpos = wrap_line(r, text, startpos, proportional_type)
+
end do
end if
-
+
break_count = break_count + 1
-
+
! Messy memory handling...
if(break_count > current_allocation) then
realloc => breaks
breaks => null()
-
+
allocate(breaks(current_allocation + 16))
breaks(1:current_allocation) = realloc
current_allocation = current_allocation + 16
deallocate(realloc)
end if
-
+
! Save an ending indicator
breaks(break_count) = last_break
-
+
end function calculate_wrapping
-
+
subroutine render_proportional(r, text, breaks)
implicit none
-
+
class(renderer)::r
character(*)::text
integer, dimension(:)::breaks
-
+
integer::startpos, endpos
integer::proportional_type
integer::break_index
-
- if(len_trim(text) == 0) then
-
+
+ if(len_trim(text) == 0) then
+
if(r%is_text_visible(" ")) then
call r%draw_proportional("")
end if
r%y = r%y + r%text_height(" ")
-
+
else
-
+
startpos = get_start_position_and_type(text, proportional_type)
-
+
break_index = 1
endpos = breaks(break_index)
if(endpos == last_break) then
endpos = len_trim(text)
end if
-
+
do while(endpos > startpos)
if(r%is_text_visible(text(startpos:endpos))) then
call r%draw_proportional(text(startpos:endpos), &
@@ -475,18 +482,18 @@ contains
end if
r%y = r%y + r%text_height(text(startpos:endpos), &
text_type=proportional_type)
-
+
! Advance string positions
startpos = endpos+1
do while(text(startpos:startpos) == ' ')
startpos = startpos + 1
end do
-
+
! Do not mark as a list item for subsequent lines
if(proportional_type == proportional_type_list_item) then
proportional_type = proportional_type_normal
end if
-
+
if(breaks(break_index) /= last_break) then
break_index = break_index + 1
endpos = breaks(break_index)
@@ -494,39 +501,39 @@ contains
endpos = len_trim(text)
end if
end if
-
+
end do
end if
-
+
end subroutine render_proportional
-
+
subroutine render_preformatted(r, text)
implicit none
-
+
class(renderer)::r
character(*)::text
-
+
if(r%is_preformatted_visible(text)) then
call r%draw_preformatted(text)
end if
r%y = r%y + r%preformatted_height(text)
-
+
end subroutine render_preformatted
-
+
subroutine render_link(r, text)
implicit none
-
+
class(renderer)::r
character(*)::text
integer::i_whitespace, d_length, i_start_display
-
+
character(len=:), allocatable::url, display
-
- ! Find the url first - just allocate the same
+
+ ! Find the url first - just allocate the same
! size as the text, good enough...
allocate(character(len=len_trim(text)) :: url)
url = adjustl(text)
-
+
! The display text occurs after the first whitespace
! in url now
i_whitespace = index(trim(url)," ")
@@ -535,14 +542,14 @@ contains
i_whitespace = index(trim(url), CHAR(9))
end if
end if
-
+
if(i_whitespace == 0) then
allocate(character(len=len_trim(url)) :: display)
display = url
else
d_length = len_trim(url) - i_whitespace + 1
allocate(character(len=d_length) :: display)
-
+
! Adjustl doesn't handle tabs, so we need to do this manually...
i_start_display = i_whitespace
do while(any([" ", char(9)] == url(i_start_display:i_start_display)))
@@ -551,57 +558,57 @@ contains
display = url(i_start_display:len_trim(url))
url = url(1:(i_whitespace-1))
end if
-
+
if(r%is_link_visible(display)) then
call r%draw_link(display, url)
end if
r%y = r%y + r%link_height(display)
-
+
deallocate(url)
deallocate(display)
-
+
end subroutine render_link
-
+
function handle_input(r, url, unit_number)
use escaper
implicit none
-
+
class(renderer)::r
character(*), intent(inout)::url
integer, intent(in)::unit_number
-
+
logical::handle_input
-
+
character(1024)::response_line
character(256)::answer
integer::question_index
-
+
rewind(unit_number)
-
+
read(unit_number, '(A1024)') response_line
question_index = 3
do while(response_line(question_index:question_index) == " " .or. &
response_line(question_index:question_index) == char(9))
-
+
question_index = question_index + 1
-
+
end do
-
+
handle_input = r%request_input(response_line(question_index:len_trim(response_line)), &
answer)
-
+
if(handle_input) then
question_index = index(url, "?")
if(question_index < 1) then
url = trim(url)//"?"
question_index = len_trim(url)
end if
-
+
call escape_string(answer)
-
+
url = url(1:question_index)//answer
end if
-
+
end function handle_input
-
+
end module render