aboutsummaryrefslogtreecommitdiff
path: root/render.f90
diff options
context:
space:
mode:
Diffstat (limited to 'render.f90')
-rw-r--r--render.f90155
1 files changed, 72 insertions, 83 deletions
diff --git a/render.f90 b/render.f90
index 335cbcb..b37eb50 100644
--- a/render.f90
+++ b/render.f90
@@ -32,6 +32,11 @@ implicit none
integer, parameter::last_break = -1
+ integer, parameter::proportional_type_normal = 0
+ integer, parameter::proportional_type_list_item = -1
+ integer, parameter::proportional_type_quotation = -2
+ integer, parameter::proportional_type_heading_1 = 1 ! For heading level, it's just positive
+
character(11), dimension(2)::base_supported_types = &
["text/plain ", &
"text/gemini" ]
@@ -57,7 +62,7 @@ implicit none
procedure(calculate_width), deferred::text_width
procedure(calculate_height), deferred::text_height
procedure(calculate_visibility), deferred::is_text_visible
- procedure(draw_text), deferred::draw_porportional
+ procedure(draw_text), deferred::draw_proportional
procedure(calculate_simple_width), deferred::preformatted_width
procedure(calculate_simple_height), deferred::preformatted_height
@@ -103,34 +108,31 @@ implicit none
end interface
abstract interface
- function calculate_width(self, text, heading, list_item)
+ function calculate_width(self, text, text_type)
import::renderer
class(renderer)::self
character(*), intent(in)::text
- integer, intent(in), optional::heading
- logical, intent(in), optional::list_item
+ integer, intent(in), optional::text_type
integer::calculate_width
end function calculate_width
end interface
abstract interface
- function calculate_height(self, text, heading, list_item)
+ function calculate_height(self, text, text_type)
import::renderer
class(renderer)::self
character(*), intent(in)::text
- integer, intent(in), optional::heading
- logical, intent(in), optional::list_item
+ integer, intent(in), optional::text_type
integer::calculate_height
end function calculate_height
end interface
abstract interface
- subroutine draw_text(self, text, heading, list_item)
+ subroutine draw_text(self, text, text_type)
import::renderer
class(renderer)::self
character(*), intent(in)::text
- integer, intent(in), optional::heading
- logical, intent(in), optional::list_item
+ integer, intent(in), optional::text_type
end subroutine draw_text
end interface
@@ -256,14 +258,13 @@ contains
end function report_unsupported_protocol
- function width_of_line(r, text, startpos, endpos, heading_level, list_item)
+ function width_of_line(r, text, startpos, endpos, proportional_type)
implicit none
class(renderer)::r
character(*), intent(in)::text
integer, intent(in)::startpos, endpos
- integer, intent(in)::heading_level
- logical, intent(in)::list_item
+ integer, intent(in)::proportional_type
integer::width_of_line
integer::my_start, my_end
@@ -282,20 +283,18 @@ contains
width_of_line = 0
else
width_of_line = r%text_width(text(my_start:my_end), &
- heading=heading_level, &
- list_item=list_item)
+ text_type=proportional_type)
end if
end function width_of_line
- function wrap_line(r, text, startpos, heading_level, list_item) result(endpos)
+ function wrap_line(r, text, startpos, proportional_type) result(endpos)
implicit none
class(renderer)::r
character(*), intent(in)::text
integer, intent(in)::startpos
- integer, intent(in)::heading_level
- logical, intent(in)::list_item
+ integer, intent(in)::proportional_type
integer::endpos
integer::my_start
integer::w
@@ -306,7 +305,7 @@ contains
end if
endpos = len_trim(text)
- w = width_of_line(r, text, my_start, endpos, heading_level, list_item)
+ w = width_of_line(r, text, my_start, endpos, proportional_type)
do while(w > r%max_width)
endpos = endpos - 1
@@ -314,11 +313,46 @@ contains
endpos = endpos - 1
end do
- w = width_of_line(r, text, my_start, endpos, heading_level, list_item)
+ w = width_of_line(r, text, my_start, endpos, proportional_type)
end do
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) == '#')
+ 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
+ startpos = startpos + 1
+ else if(text(1:1) == '>') then
+ proportional_type = proportional_type_quotation
+ startpos = startpos + 1
+ end if
+ end if
+
+ ! If either occurred, advance past whitespace
+ if(proportional_type /= proportional_type_normal) then
+ do while(text(startpos:startpos) == ' ' .or. text(startpos:startpos) == char(9))
+ startpos = startpos + 1
+ end do
+ end if
+
+ end function get_start_position_and_type
+
function calculate_wrapping(r, text) result(breaks)
implicit none
@@ -327,8 +361,8 @@ contains
integer, dimension(:), pointer::breaks
integer::startpos, endpos
- integer::heading_level
- logical::list_item
+ integer::proportional_type
+ logical::list_item, quotation
integer::current_allocation
integer::break_count
@@ -340,32 +374,9 @@ contains
if(len_trim(text) > 0) then
- startpos = 1
-
- ! Check for headings first
- heading_level = 0
- do while(text(startpos:startpos) == '#')
- heading_level = heading_level + 1
- startpos = startpos + 1
- end do
-
- ! Or a list item
- list_item = .FALSE.
- if(heading_level == 0) then
- list_item = (text(1:1) == '*')
- if(list_item) then
- startpos = startpos + 1
- end if
- end if
+ startpos = get_start_position_and_type(text, proportional_type)
- ! If either occurred, advance past whitespace
- if(heading_level > 0 .or. list_item) then
- do while(text(startpos:startpos) == ' ' .or. text(startpos:startpos) == char(9))
- startpos = startpos + 1
- end do
- end if
-
- endpos = wrap_line(r, text, startpos, heading_level, list_item)
+ endpos = wrap_line(r, text, startpos, proportional_type)
do while(endpos > startpos)
! Save this break
@@ -392,8 +403,11 @@ contains
end do
! Do not mark as a list item for subsequent lines
- list_item = .FALSE.
- endpos = wrap_line(r, text, startpos, heading_level, list_item)
+ 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
@@ -423,44 +437,19 @@ contains
integer, dimension(:)::breaks
integer::startpos, endpos
- integer::heading_level
- logical::list_item
-
+ integer::proportional_type
integer::break_index
if(len_trim(text) == 0) then
if(r%is_text_visible(" ")) then
- call r%draw_porportional("")
+ call r%draw_proportional("")
end if
r%y = r%y + r%text_height(" ")
else
- startpos = 1
-
- ! Check for headings first
- heading_level = 0
- do while(text(startpos:startpos) == '#')
- heading_level = heading_level + 1
- startpos = startpos + 1
- end do
-
- ! Or a list item
- list_item = .FALSE.
- if(heading_level == 0) then
- list_item = (text(1:1) == '*')
- if(list_item) then
- startpos = startpos + 1
- end if
- end if
-
- ! If either occurred, advance past whitespace
- if(heading_level > 0 .or. list_item) then
- do while(text(startpos:startpos) == ' ' .or. text(startpos:startpos) == char(9))
- startpos = startpos + 1
- end do
- end if
+ startpos = get_start_position_and_type(text, proportional_type)
break_index = 1
endpos = breaks(break_index)
@@ -470,13 +459,11 @@ contains
do while(endpos > startpos)
if(r%is_text_visible(text(startpos:endpos))) then
- call r%draw_porportional(text(startpos:endpos), &
- heading=heading_level, &
- list_item=list_item)
+ call r%draw_proportional(text(startpos:endpos), &
+ text_type=proportional_type)
end if
r%y = r%y + r%text_height(text(startpos:endpos), &
- heading=heading_level, &
- list_item=list_item)
+ text_type=proportional_type)
! Advance string positions
startpos = endpos+1
@@ -485,7 +472,9 @@ contains
end do
! Do not mark as a list item for subsequent lines
- list_item = .FALSE.
+ 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