module appgraphics_filo use filo implicit none type, extends(editorConfig) :: apEditorConfig integer::window integer::x, y, w, h end type apEditorConfig contains function initApEditor(win, x, y, w, h) result(E) use appgraphics, only: getmaxx, getmaxy implicit none integer, intent(in)::win integer, intent(in), optional::x, y, w, h type(apEditorConfig)::E call initEditor(E) E%window = win if(present(x)) then E%x = x else E%x = 0 end if if(present(y)) then E%y = y else E%y = 0 end if if(present(w)) then E%w = w else E%w = getmaxx() end if if(present(h)) then E%h = h else E%h = getmaxy() end if call updateApEditorSize(E) end function initApEditor subroutine updateApEditorSize(E) use appgraphics implicit none class(apEditorConfig), intent(inout)::E E%screencols = 0 do while(textwidth(repeat('X', E%screencols+1)) < E%w) E%screencols = E%screencols + 1 end do E%screenrows = E%h / textheight('XXX') E%cx = max(E%cx, E%screencols) E%cy = max(E%cy, E%screenrows) end subroutine updateApEditorSize subroutine drawApEditor(E) use appgraphics implicit none class(apEditorConfig), intent(inout)::E integer::irow, icol, icollast integer::x, y, rh character(len=:), pointer::row_text call setcurrentwindow(E%window) call resetviewport() call setviewport(E%x, E%y, E%x+E%w, E%y+E%h, .TRUE.) call clearviewport() ! We used to compute this per line, but the text height calcs are way off rh = textheight('XXXyy') y = 0 do irow = 1+E%rowoff, E%rowoff + E%screenrows x = 0 rh = 0 row_text => E%row(irow)%string_pointer() if(.not. associated(row_text)) then rh = textheight('XXX') else if(E%coloff+1 > len(row_text)) then rh = textheight('XXX') else icol = 1 - E%coloff icollast = min(icol+E%screencols, len(row_text)) call outtextxy(x, y, row_text(icol:icollast)) rh = textheight(row_text(icol:icollast)) end if ! if(irow == E%cy .and. icol == E%cx) then ! call bar(x, y, x+3, y+rh) ! end if end if ! Cursor if(irow - E%rowoff == E%cy) then if(.not. associated(row_text) .or. E%cx == 1) then x = 0 else ! Width calculations are all messed up by trimming ! being performed in textwidth if(len(row_text) < icol+E%cx-2) then E%cx = len(row_text) - icol + 2 end if icollast = icol+E%cx-2 x = index(row_text(icol:icollast), ' ') do while(x > 0) x = x + icol - 1 row_text(x:x) = '_' x = index(row_text(icol:icollast), ' ') end do x = textwidth(row_text(icol:icollast)) end if call bar(x, y+rh-1, x+3, y+1) end if if(associated(row_text)) then deallocate(row_text) row_text => null() end if y = y + rh end do call resetviewport() end subroutine drawApEditor end module appgraphics_filo