@@ -20,6 +20,9 @@ module fpm_compile_commands
20
20
21
21
contains
22
22
23
+ ! > Operation
24
+ procedure :: destroy = > compile_command_destroy
25
+
23
26
! > Serialization interface
24
27
procedure :: serializable_is_same = > compile_command_is_same
25
28
procedure :: dump_to_toml = > compile_command_dump_toml
@@ -34,10 +37,14 @@ module fpm_compile_commands
34
37
contains
35
38
36
39
! > Operation
37
- procedure :: destroy = > cct_destroy
38
- procedure :: register = > cct_register
40
+ procedure :: destroy = > cct_destroy
39
41
procedure :: write = > cct_write
40
42
43
+ procedure , private :: cct_register
44
+ procedure , private :: cct_register_object
45
+ generic :: register = > cct_register, &
46
+ cct_register_object
47
+
41
48
! > Serialization interface
42
49
procedure :: serializable_is_same = > cct_is_same
43
50
procedure :: dump_to_toml = > cct_dump_toml
@@ -47,6 +54,18 @@ module fpm_compile_commands
47
54
end type compile_command_table_t
48
55
49
56
contains
57
+
58
+ ! > Cleanup compile command
59
+ elemental subroutine compile_command_destroy (self )
60
+
61
+ ! > Instance of the serializable object
62
+ class(compile_command_t), intent (inout ) :: self
63
+
64
+ if (allocated (self% directory% s))deallocate (self% directory% s)
65
+ if (allocated (self% arguments))deallocate (self% arguments)
66
+ if (allocated (self% file% s))deallocate (self% file% s)
67
+
68
+ end subroutine compile_command_destroy
50
69
51
70
! > Dump compile_command_t to toml table
52
71
subroutine compile_command_dump_toml (self , table , error )
@@ -60,6 +79,8 @@ subroutine compile_command_dump_toml(self, table, error)
60
79
! > Error handling
61
80
type (error_t), allocatable , intent (out ) :: error
62
81
82
+ call self% destroy()
83
+
63
84
call set_string(table, " directory" , self% directory, error, ' compile_command_t' )
64
85
if (allocated (error)) return
65
86
call set_list(table, " arguments" , self% arguments, error)
@@ -256,13 +277,29 @@ subroutine cct_register(self, command, error)
256
277
arguments = [(string_t(trim (args(i))), i= 1 ,n)], &
257
278
file = string_t(source_file))
258
279
259
- if (allocated (self% command)) then
260
- self% command = [self% command, cmd]
261
- else
262
- allocate (self% command(1 ), source= cmd)
263
- end if
280
+ ! Add it to the structure
281
+ call cct_register_object(self, cmd, error)
264
282
265
283
end subroutine cct_register
284
+
285
+ pure subroutine cct_register_object (self , command , error )
286
+
287
+ ! > Instance of the serializable object
288
+ class(compile_command_table_t), intent (inout ) :: self
289
+
290
+ ! > Data structure
291
+ type (compile_command_t), intent (in ) :: command
292
+
293
+ ! > Error handling
294
+ type (error_t), allocatable , intent (out ) :: error
295
+
296
+ if (allocated (self% command)) then
297
+ self% command = [self% command, command]
298
+ else
299
+ allocate (self% command(1 ), source= command)
300
+ end if
301
+
302
+ end subroutine cct_register_object
266
303
267
304
! > Dump compile_command_table_t to toml table
268
305
subroutine cct_dump_toml (self , table , error )
0 commit comments