aboutsummaryrefslogtreecommitdiff
path: root/captain/api.f90
blob: 9e921855f76b267aa6a81eeb97d249271aae7458 (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
module api_handling
implicit none

    character(*), parameter::RESPONSE_JSON_OKAY = '{"status": "okay"}'
    character(*), parameter::RESPONSE_JSON_IDLE = '{"status": "idle"}'

contains

    subroutine handle_task_request(req)
    use server_response
    use captain_db
    implicit none
    
        class(request)::req
        character(8)::job_text, task_text
        integer::job_i, task_i, ierr
        
        call req%path_component(5, job_text)
        read(job_text, *, iostat=ierr) job_i
        
        if(ierr == 0) then
            call req%path_component(7, task_text)
            read(task_text, *, iostat=ierr) task_i
            if(ierr == 0) then
                if(req%query_string == "starting" .or. req%query_string == "inprogress") then
                    call update_task_status(job_i, task_i, JOB_STATUS_WORKING)
                else if(req%query_string == "complete") then
                    call update_task_status(job_i, task_i, JOB_STATUS_SUCCESS)
                else if(req%query_string == "failed") then
                    call update_task_status(job_i, task_i, JOB_STATUS_FAILURE)
                end if
            end if
        end if
        
    end subroutine handle_task_request
    
    function api_request_gemini(req) result(resp)
    use server_response
    use captain_db
    use special_filenames
    implicit none
    
        type(request), intent(in)::req
        type(response)::resp
        
        character(8)::job_text
        character(PLAYER_NAME_LENGTH)::player
        integer::job_i, player_i, instruction_i, ierr

        ! Complete - "/api/player/{name}/job/{jobid}/complete"
        ! Failed   - "/api/player/{name}/job/{jobid}/failed"
        ! Task     - "/api/player/{name}/job/{jobid}/task/{task num}"
        if(trim(req%component(2)) == "player" .and. trim(req%component(4)) == "job") then
            call req%path_component(5, job_text)
            read(job_text, *, iostat=ierr) job_i
            
            if(ierr == 0 .and. .not. is_final_job_status(job_i)) then
                if(trim(req%component(6)) == "complete") then
                    call update_job_status(job_i, JOB_STATUS_SUCCESS)
                else if(trim(req%component(6)) == "failure") then
                    call update_job_status(job_i, JOB_STATUS_FAILURE)
                end if
            end if
            
            if(ierr == 0 .and. trim(req%component(6)) == "task") then
                call handle_task_request(req)
            end if
            
            resp%code = GEMINI_CODE_SUCCESS
            call resp%set_body_contents(RESPONSE_JSON_OKAY)
            resp%body_mimetype = "application/json"
         
        ! Checkin - /api/player/{name}/checkin.json
        else if(trim(req%component(2)) == "player" .and. trim(req%component(4)) == "checkin.json") then
            ! Check for pending jobs
            call req%path_component(3, player)
            player_i = get_player_id(player)
            
            job_i = get_pending_job_for_player(player_i)
            if(job_i < 0) then
                resp%code = GEMINI_CODE_SUCCESS
                call resp%set_body_contents(RESPONSE_JSON_IDLE) 
            else
                resp%code = GEMINI_CODE_SUCCESS
                instruction_i = get_job_instruction(job_i)
                resp%body_filename => get_instructions_static_filename(instruction_i)
                resp%temporary_file = .false.
                resp%body_mimetype = "application/json"
            end if
        end if
    
    end function api_request_gemini

    function api_request_titan(req) result(resp)
    use server_response
    use special_filenames
    implicit none
    
        type(titan_request), intent(in)::req
        type(response)::resp
        
        character(len=:), pointer::fullpath
        character(12)::job_text, task_text
        integer::job_id, task_num, ierr
        
        fullpath => null()
        
        ! Task     - "/api/player/{name}/job/{jobid}/task/{task num}"
        if(trim(req%component(2)) == "player" .and. &
           trim(req%component(4)) == "job" .and. &
           trim(req%component(6)) == "task") then
           
            call req%path_component(5, job_text)
            read(job_text, *, iostat=ierr) job_id
            if(ierr /= 0) then
                resp%code = GEMINI_CODE_PERMFAIL
                return
            end if
            
            call req%path_component(5, task_text)
            read(task_text, *, iostat=ierr) task_num
            if(ierr /= 0) then
                resp%code = GEMINI_CODE_PERMFAIL
                return
            end if
            
            call handle_task_request(req)
            
            fullpath => get_task_result_static_filename(job_id, task_num)

        end if
            
        if(associated(fullpath)) then
        
            ! Write the file
            call req%write_to(fullpath)
        
            resp%code = GEMINI_CODE_SUCCESS
            call resp%set_body_contents(RESPONSE_JSON_OKAY)
            resp%body_mimetype = "application/json"
        
        else
            
            resp%code = GEMINI_CODE_PERMFAIL
        
        end if
        
    end function api_request_titan

end module api_handling