aboutsummaryrefslogtreecommitdiff
path: root/captain/requtils.f90
blob: 23df37af8efc35f04071f3a455dd9bf7156ac694 (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
149
150
151
152
153
154
155
156
module request_utils
implicit none

contains

    pure function success_code(req)
    use gemini_protocol, only: GEMINI_SUCCESS => STATUS_SUCCESS
    use http, only: HTTP_SUCCESS => HTTP_CODE_SUCCESS
    use server_response, only: request
    implicit none
    
        class(request), intent(in)::req
        integer::success_code
    
        if(req%protocol == 'gemini') then
            success_code = GEMINI_SUCCESS
        else
            success_code = HTTP_SUCCESS
        end if
        
    end function success_code

    pure function notfound_code(req)
    use gemini_protocol, only: GEMINI_FAIL => STATUS_PERMFAIL
    use http, only: HTTP_FAIL => HTTP_CODE_NOTFOUND
    use server_response, only: request
    implicit none
    
        class(request), intent(in)::req
        integer::notfound_code
    
        if(req%protocol == 'gemini') then
            notfound_code = GEMINI_FAIL
        else
            notfound_code = HTTP_FAIL
        end if
        
    end function notfound_code

    subroutine basic_mimetype(actual_filename, mimetype) 
    use utilities, only: get_one_line_output_shell_command
    implicit none
    
        character(*), intent(in)::actual_filename
        character(*), intent(out)::mimetype
        
        logical::exists
        
        ! Check for gemini first since it's fake...
        if(index(actual_filename, ".gmi") /= 0) then
            mimetype = "text/gemini"
            
        else
        
            inquire(name=actual_filename, exist=exists)
            if(exists) then
            
                call get_one_line_output_shell_command("mimetype -b "//trim(actual_filename), mimetype)
            
            else
            
                ! If it doesn't exist, use the extension dumbly
                if(index(actual_filename, ".txt") /= 0) then
                    mimetype = "text/plain"
                    
                else if(index(actual_filename, ".json") /= 0) then
                    mimetype = "text/plain"
                
                else if(index(actual_filename, ".html") /= 0) then
                    mimetype = "text/html"
                
                else if(index(actual_filename, ".css") /= 0) then
                    mimetype = "text/css"
                    
                ! Just a catch-all, whatever...
                else
                    mimetype = "application/octet-stream"
                    
                end if
            
            end if
        
        end if
    
    end subroutine basic_mimetype

    function is_request_static(req)
    use server_response
    use logging
    implicit none
    
        class(request), intent(in)::req
        logical::is_request_static
        character(64)::first, last
        
        character(4)::ext
        integer::j
        
        call req%path_component(1, first)
        call req%last_component(last)
        
        j = index(last, ".", back=.true.)
        if(j > 0) then
            ext = last(j+1:len_trim(last))
        else
            ext = " "
        end if
        
        call write_log("Static check: "//trim(first), LOG_DEBUG)
        
        is_request_static = ((trim(first) == "releases") .or. &
                             (trim(first) == "uploads") .or. &
                             (trim(first) == "results") .or. &
                             (trim(first) == "static") .or. &
                             (trim(first) == "favicon.txt") .or. &
                             (trim(first) == "instructions" .and. trim(ext) == "json"))
        
    end function is_request_static

    function request_static(req) result(resp)
    use logging
    use config
    use utilities
    use server_response
    use special_filenames
    implicit none
    
        class(request), intent(in)::req
        type(response)::resp
        character(64)::category
        character(256)::filename
        logical::exists
    
        resp%temporary_file = .false.
        
        call req%path_component(1, category)
        call req%path_component(2, filename)
        
        resp%body_filename => get_special_full_filename(trim(category), trim(filename))
    
        inquire(name=resp%body_filename, exist=exists)
        if(.not. exists) then
        
            resp%code = notfound_code(req)
            call write_log("File did not exist: "//resp%body_filename, LOG_NORMAL)
            
        else
            
            resp%code = success_code(req)
            call basic_mimetype(resp%body_filename, resp%body_mimetype)

        end if
    
    end function request_static

end module request_utils