aboutsummaryrefslogtreecommitdiff
path: root/render.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-02-18 09:07:32 -0500
committerJeffrey Armstrong <jeff@approximatrix.com>2021-02-18 09:10:27 -0500
commit2499f1720602a9010f4618f0b686f077febbdf55 (patch)
treea7bfbf464fcd62fbd5fd4cc9a9b94d0390980afb /render.f90
parent81bc5140a2961e97ecacd2296da9f3111f7c91de (diff)
downloadLR-87-2499f1720602a9010f4618f0b686f077febbdf55.tar.gz
LR-87-2499f1720602a9010f4618f0b686f077febbdf55.zip
Preformatted text should no longer wrap, and the stopping point for printing preformatted text is now calculated. Removed double-accounting of borders in text width calculations.
Diffstat (limited to 'render.f90')
-rw-r--r--render.f9031
1 files changed, 28 insertions, 3 deletions
diff --git a/render.f90 b/render.f90
index 9027f83..5d946c7 100644
--- a/render.f90
+++ b/render.f90
@@ -377,7 +377,23 @@ 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
@@ -515,16 +531,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