Skip to content

Commit cfc805a

Browse files
committed
compile command: destroy object
1 parent a6c4483 commit cfc805a

File tree

1 file changed

+44
-7
lines changed

1 file changed

+44
-7
lines changed

src/fpm_compile_commands.F90

Lines changed: 44 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,9 @@ module fpm_compile_commands
2020

2121
contains
2222

23+
!> Operation
24+
procedure :: destroy => compile_command_destroy
25+
2326
!> Serialization interface
2427
procedure :: serializable_is_same => compile_command_is_same
2528
procedure :: dump_to_toml => compile_command_dump_toml
@@ -34,10 +37,14 @@ module fpm_compile_commands
3437
contains
3538

3639
!> Operation
37-
procedure :: destroy => cct_destroy
38-
procedure :: register => cct_register
40+
procedure :: destroy => cct_destroy
3941
procedure :: write => cct_write
4042

43+
procedure, private :: cct_register
44+
procedure, private :: cct_register_object
45+
generic :: register => cct_register, &
46+
cct_register_object
47+
4148
!> Serialization interface
4249
procedure :: serializable_is_same => cct_is_same
4350
procedure :: dump_to_toml => cct_dump_toml
@@ -47,6 +54,18 @@ module fpm_compile_commands
4754
end type compile_command_table_t
4855

4956
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
5069

5170
!> Dump compile_command_t to toml table
5271
subroutine compile_command_dump_toml(self, table, error)
@@ -60,6 +79,8 @@ subroutine compile_command_dump_toml(self, table, error)
6079
!> Error handling
6180
type(error_t), allocatable, intent(out) :: error
6281

82+
call self%destroy()
83+
6384
call set_string(table, "directory", self%directory, error, 'compile_command_t')
6485
if (allocated(error)) return
6586
call set_list(table, "arguments", self%arguments, error)
@@ -256,13 +277,29 @@ subroutine cct_register(self, command, error)
256277
arguments = [(string_t(trim(args(i))), i=1,n)], &
257278
file = string_t(source_file))
258279

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)
264282

265283
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
266303

267304
!> Dump compile_command_table_t to toml table
268305
subroutine cct_dump_toml(self, table, error)

0 commit comments

Comments
 (0)