aboutsummaryrefslogtreecommitdiff
path: root/layout.f90
diff options
context:
space:
mode:
Diffstat (limited to 'layout.f90')
-rw-r--r--layout.f9034
1 files changed, 32 insertions, 2 deletions
diff --git a/layout.f90 b/layout.f90
index 685d646..714d62b 100644
--- a/layout.f90
+++ b/layout.f90
@@ -32,7 +32,7 @@ implicit none
character(len=:), allocatable::text
integer::line_type
- integer, dimension(128)::breaks
+ integer, dimension(:), pointer::breaks
type(line), pointer::next
end type line
@@ -56,10 +56,18 @@ contains
do while(laying_out)
+ if(walker%line_type == line_type_text .and. .not. associated(walker%breaks)) then
+ walker%breaks => calculate_wrapping(rendering_engine, walker%text)
+ end if
+
+ if(associated(walker%breaks)) then
+ Print *, "Associated"
+ end if
+
select case (walker%line_type)
case (line_type_text)
- call render_proportional(rendering_engine, walker%text)
+ call render_proportional(rendering_engine, walker%text, walker%breaks)
case (line_type_preformatted)
call render_preformatted(rendering_engine, walker%text)
@@ -78,6 +86,26 @@ contains
end subroutine layout_lines
+ subroutine clear_line_breaks(first_line)
+ implicit none
+
+ type(line), intent(inout), pointer::first_line
+ type(line), pointer::walker
+
+ walker => first_line
+
+ do while(associated(walker))
+ if(associated(walker%breaks)) then
+ deallocate(walker%breaks)
+ walker%breaks => null()
+ end if
+
+ walker => walker%next
+
+ end do
+
+ end subroutine clear_line_breaks
+
subroutine free_lines(first_line)
implicit none
@@ -85,6 +113,8 @@ contains
type(line), pointer::walker, past
+ call clear_line_breaks(first_line)
+
walker => first_line
do while(associated(walker))