aboutsummaryrefslogtreecommitdiff
path: root/render.f90
diff options
context:
space:
mode:
Diffstat (limited to 'render.f90')
-rw-r--r--render.f9060
1 files changed, 55 insertions, 5 deletions
diff --git a/render.f90 b/render.f90
index 9027f83..7a65127 100644
--- a/render.f90
+++ b/render.f90
@@ -48,6 +48,7 @@ implicit none
integer::y
integer::max_width
+ character(4)::favicon
contains
@@ -55,6 +56,8 @@ implicit none
procedure::type_supported
procedure::status_ready
procedure::report_unsupported_protocol
+ procedure::set_favicon
+ procedure::clear_favicon
procedure(initialize), deferred::initialize
procedure(prepare_for_layout), deferred::prepare_for_layout
@@ -267,6 +270,25 @@ contains
end function report_unsupported_protocol
+ subroutine set_favicon(self, f)
+ implicit none
+
+ class(renderer)::self
+ character(*), intent(in)::f
+
+ self%favicon = f
+
+ end subroutine set_favicon
+
+ subroutine clear_favicon(self)
+ implicit none
+
+ class(renderer)::self
+
+ self%favicon = " "
+
+ end subroutine clear_favicon
+
function width_of_line(r, text, startpos, endpos, proportional_type)
implicit none
@@ -377,7 +399,24 @@ contains
end if
end function get_start_position_and_type
+
+ function calculate_stop(r, text) result(breaks)
+ implicit none
+
+ class(renderer)::r
+ character(*), intent(in)::text
+ integer, dimension(:), pointer::breaks
+
+ allocate(breaks(1))
+
+ breaks(1) = len_trim(text)
+
+ do while(r%preformatted_width(text(1:breaks(1))) > r%max_width)
+ breaks(1) = breaks(1) - 1
+ end do
+ end function calculate_stop
+
function calculate_wrapping(r, text) result(breaks)
implicit none
@@ -402,7 +441,8 @@ contains
startpos = get_start_position_and_type(text, proportional_type)
endpos = wrap_line(r, text, startpos, proportional_type)
- do while(endpos > startpos)
+
+ do while(endpos >= startpos)
! Save this break
break_count = break_count + 1
@@ -465,6 +505,7 @@ contains
integer::startpos, endpos
integer::proportional_type
integer::break_index
+ integer::h
if(len_trim(text) == 0) then
@@ -483,7 +524,7 @@ contains
endpos = len_trim(text)
end if
- do while(endpos > startpos)
+ do while(endpos >= startpos)
if(r%is_text_visible(text(startpos:endpos))) then
call r%draw_proportional(text(startpos:endpos), &
text_type=proportional_type)
@@ -515,16 +556,25 @@ contains
end subroutine render_proportional
- subroutine render_preformatted(r, text)
+ subroutine render_preformatted(r, text, stoppoint)
implicit none
class(renderer)::r
character(*)::text
+ integer, intent(in), optional::stoppoint
+
+ integer::i
+
+ if(present(stoppoint)) then
+ i = stoppoint
+ else
+ i = len_trim(text)
+ end if
if(r%is_preformatted_visible(text)) then
- call r%draw_preformatted(text)
+ call r%draw_preformatted(text(1:i))
end if
- r%y = r%y + r%preformatted_height(text)
+ r%y = r%y + r%preformatted_height(text(1:i))
end subroutine render_preformatted