summaryrefslogtreecommitdiff
path: root/apfilo.f90
blob: 2efbe1c93bf3153513b01cb727cbd6a77c6d7b32 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
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