aboutsummaryrefslogtreecommitdiff
path: root/ag_render.f90
diff options
context:
space:
mode:
Diffstat (limited to 'ag_render.f90')
-rw-r--r--ag_render.f9091
1 files changed, 70 insertions, 21 deletions
diff --git a/ag_render.f90 b/ag_render.f90
index e964df3..b91a416 100644
--- a/ag_render.f90
+++ b/ag_render.f90
@@ -34,6 +34,7 @@ implicit none
integer, volatile::ag_render_event
integer, volatile::scroll_position
+ integer, volatile::wheel_movement
integer, parameter::ag_render_event_none = 0
integer, parameter::ag_render_event_closed = 1
@@ -85,6 +86,9 @@ implicit none
! Needed to compute document height
integer::initial_y
+
+ ! Page height
+ integer::page_height
! An error has occurred, so render blank
logical::render_blank
@@ -135,6 +139,9 @@ implicit none
procedure :: report_unsupported_protocol => ag_report_unsupported_protocol
procedure :: set_favicon => ag_set_favicon
+
+ procedure :: rendering_height_available => ag_rendering_height_available
+ procedure :: scroll_max_value => ag_scroll_max_value
end type appgraphics_renderer
@@ -214,13 +221,7 @@ contains
integer::x, y
- scroll_position = scroll_position - (x/35)
- if(scroll_position < 0) then
- scroll_position = 0
- else if(scroll_position > 100) then
- scroll_position = 100
- end if
-
+ wheel_movement = wheel_movement + x
ag_render_event = ag_render_event_wheel
call stopidle()
@@ -231,6 +232,7 @@ contains
implicit none
integer::x
+
scroll_position = x
ag_render_event = ag_render_event_scroll
call stopidle()
@@ -320,14 +322,16 @@ contains
call setfillstyle(SOLID_FILL, LIGHTGRAY)
call setbkcolor(LIGHTGRAY)
call setcolor(BLACK)
- call settextstyle(SYMBOLS_FONT, HORIZ_DIR, scaledpi(14))
+ call settextstyle(SANS_SERIF_FONT, HORIZ_DIR, scaledpi(18))
end do
call setactivepage(active_page)
! Draw the buttons first
x = 5
if(self%back_button_id < 0) then
- self%back_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), CHAR(231), back_button_callback)
+ self%back_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), &
+ ACHAR(240)//ACHAR(159)//ACHAR(161)//ACHAR(184), &
+ back_button_callback)
else
call setbuttonposition(self%back_button_id, x, 2, scaledpi(40), scaledpi(20))
end if
@@ -349,30 +353,36 @@ contains
! Clears any drawing operations for controls quickly
ignored = switch_to_thread()
- call settextstyle(SYMBOLS_FONT, HORIZ_DIR, 14)
+ call settextstyle(SANS_SERIF_FONT, HORIZ_DIR, scaledpi(18))
x = x + 10 + address_width
if(self%go_button_id < 0) then
- self%go_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), CHAR(232), go_button_callback)
+ self%go_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), &
+ ACHAR(240)//ACHAR(159)//ACHAR(161)//ACHAR(186), &
+ go_button_callback)
else
call setbuttonposition(self%go_button_id, x, 2, scaledpi(40), scaledpi(20))
end if
- call settextstyle(SYMBOLS_FONT, HORIZ_DIR, scaledpi(18))
+ call settextstyle(SANS_SERIF_FONT, HORIZ_DIR, scaledpi(20))
! If we're not expanding, just draw these buttons in order
if(.not. myexpand) then
x = getmaxx() - scaledpi(95)
if(self%fave_button_id < 0) then
- self%fave_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), CHAR(171), fave_button_callback)
+ self%fave_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), &
+ ACHAR(226)//ACHAR(152)//ACHAR(133), &
+ fave_button_callback)
else
call setbuttonposition(self%fave_button_id, x, 2, scaledpi(40), scaledpi(20))
end if
x = x + scaledpi(50)
if(self%internal_button_id < 0) then
- self%internal_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), CHAR(62), internal_button_callback)
+ self%internal_button_id = createbutton(x, 2, scaledpi(40), scaledpi(20), &
+ ACHAR(226)//ACHAR(156)//ACHAR(135), &
+ internal_button_callback)
else
call setbuttonposition(self%internal_button_id, x, 2, scaledpi(40), scaledpi(20))
end if
@@ -584,14 +594,44 @@ contains
end subroutine ag_prepare_for_layout
+ function ag_rendering_height_available(self)
+ use appgraphics, only: getmaxy
+ implicit none
+
+ class(appgraphics_renderer), intent(in)::self
+ integer::ag_rendering_height_available
+
+ ag_rendering_height_available = getmaxy() - self%status_bar_height - &
+ self%address_bar_height - 1
+
+ end function ag_rendering_height_available
+
+ function ag_scroll_max_value(self)
+ implicit none
+
+ class(appgraphics_renderer), intent(in)::self
+ integer::ag_scroll_max_value
+
+ ag_scroll_max_value = max(0, self%page_height - self%rendering_height_available())
+
+ end function ag_scroll_max_value
+
subroutine ag_layout_complete(self)
use appgraphics, only: swapbuffers
implicit none
class(appgraphics_renderer)::self
+ integer::nPages
call swapbuffers()
+ if(self%page_height == 0) then
+ self%page_height = self%y + self%initial_y
+ nPages = self%rendering_height_available()
+ call setscrollrange(self%scroll_id, 0, self%scroll_max_value()+nPages)
+ call setscrollpagesize(self%scroll_id, nPages)
+ end if
+
end subroutine ag_layout_complete
subroutine ag_new_page(self)
@@ -601,11 +641,13 @@ contains
self%y = 0
scroll_position = 0
+ wheel_movement = 0
call setscrollposition(self%scroll_id, 0)
ag_render_event = ag_render_event_none
self%title_guessed = .false.
+ self%page_height = 0
end subroutine ag_new_page
@@ -925,9 +967,6 @@ contains
logical::expanding_horizontally
- ! For scrolling
- integer::doclength
-
! Resize can be laggy, so ensure it actually was finalized
if(self%max_width /= compute_max_width(self)) then
ag_render_event = ag_render_event_resize
@@ -970,15 +1009,25 @@ contains
call clearmouseclick(MOUSE_MOVE)
case(ag_render_event_wheel)
+ scroll_position = scroll_position - &
+ (wheel_movement/120)* &
+ self%text_height("Scrolled Example", proportional_type_normal)
+
+ ! Limit
+ scroll_position = max(0, scroll_position)
+ scroll_position = min(self%scroll_max_value(), &
+ scroll_position)
+
call setscrollposition(self%scroll_id, scroll_position)
- doclength = self%y - self%initial_y
- self%y = (doclength * scroll_position) / (-100)
+ self%y = -1*scroll_position
ag_action = render_action_layout
+
+ wheel_movement = 0
case(ag_render_event_scroll)
- doclength = self%y - self%initial_y
- self%y = (doclength * scroll_position) / (-100)
+
+ self%y = -1*scroll_position
ag_action = render_action_layout
case(ag_render_event_resize)