aboutsummaryrefslogtreecommitdiff
path: root/player/instructions.f90
blob: 8c671c468a5f6bb19aec001eb21a2451672b8cee (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
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
module instructions
implicit none

contains

    function parse_instructions(filename) result(j)
    use json_module
    implicit none
    
        type(json_file)::j
        character(*), intent(in)::filename
        
        call j%initialize()
        call j%load_file(filename=filename)
        
    end function parse_instructions
    
    subroutine destroy_instructions(j)
    use json_module
    implicit none
    
        type(json_file)::j
        call j%destroy()
    
    end subroutine destroy_instructions
    
    subroutine get_description(j, description)
    use json_module
    implicit none
    
        class(json_file)::j
        character(*), intent(out)::description
        character(len=:), allocatable::json_string_value
        logical::found
        
        call j%get("description", json_string_value, found)
        if(.not. found .or. .not. allocated(json_string_value)) then
            description = "(instructions)"
        else
            description = json_string_value
        end if
        
    end subroutine get_description
    
    function get_task_count(j) result(n)
    use json_module
    implicit none
    
        class(json_file)::j
        integer::n
        
        type(json_value), pointer ::server
        logical::found
        character(3)::index_string
        n = 0
        
        found = .true.
        do while(found)
            n = n + 1
            write(index_string, '(I3)') n
            call j%get("tasks("//trim(index_string)//")", server, found)
        end do
        n = n - 1
        
    end function get_task_count
    
    pure subroutine task_component(i, component, label)
    implicit none
        
        integer, intent(in)::i
        character(*), intent(in)::component
        character(*), intent(out)::label
        
        write(label, '(A6,I3,A2)') "tasks(", i, ")."
        label = label//trim(component)
    
    end subroutine task_component
    
    function get_task_string(j, i, component, res) result(found)
    use json_module
    implicit none
        
        class(json_file)::j
        integer, intent(in)::i
        character(*), intent(in)::component
        character(*), intent(out)::res
        logical::found
        
        character(len=64)::label
        character(len=:), allocatable::json_string_value
        
        call task_component(i, component, label)
        
        call j%get(trim(label), json_string_value, found)
        
        if(allocated(json_string_value)) then
            res = json_string_value
        end if
        
    end function get_task_string
    
    subroutine get_task_name(j, i, description)
    use json_module
    implicit none
    
        class(json_file)::j
        character(*), intent(out)::description
        integer, intent(in)::i
        logical::found

        found = get_task_string(j, i, "name", description)
        
        if(.not. found) then
            write(description, '(A4, 1X, I3)') "Task", i
        end if
        
    end subroutine get_task_name
    
    subroutine get_task_operation(j, i, op)
    use json_module
    implicit none
    
        class(json_file)::j
        character(*), intent(out)::op
        integer, intent(in)::i
        logical::found

        found = get_task_string(j, i, "operation", op)
        
        if(.not. found) then
            op = " "
        end if
        
    end subroutine get_task_operation

    function perform_task(j, i, capture_filename) result(success)
    use json_module
    use tasks
    use utilities
    implicit none
    
        class(json_file)::j
        integer, intent(in)::i
        character(len=:), pointer, intent(out)::capture_filename
        logical::success
        
        character(32)::operation
        character(256)::url
        character(256)::filename
        
        logical, dimension(4)::found
        
        call get_task_operation(j, i, operation)
        
        found = .true.
        capture_filename => null()
        
        if(trim(operation) == "upload") then
            found(1) = get_task_string(j, i, "url", url)
            found(2) = get_task_string(j, i, "filename", filename)
            if(.not. all(found,1)) then
                success = .false.
            else
                success = upload(url, filename)
            end if
        
        else if(trim(operation) == "download") then
            found(1) = get_task_string(j, i, "url", url)
            found(2) = get_task_string(j, i, "filename", filename)
            if(.not. all(found,1)) then
                success = .false.
            else
                success = download(url, filename)
            end if
        
        else if(trim(operation) == "git_update") then
            capture_filename => generate_temporary_filename()
        
            found(1) = get_task_string(j, i, "url", url)
            found(2) = get_task_string(j, i, "filename", filename)
            if(.not. all(found,1)) then
                success = .false.
            else
                success = download(url, filename)
            end if
        
        
        else if(trim(operation) == "shell") then
        
        
        else if(trim(operation) == "delete_tree") then
        
        
        end if
        
    end function perform_task
    
end module instructions