Skip to content

Commit 18d0ce3

Browse files
committed
test serialization
1 parent cfc805a commit 18d0ce3

File tree

2 files changed

+15
-14
lines changed

2 files changed

+15
-14
lines changed

src/fpm_compile_commands.F90

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -79,12 +79,10 @@ subroutine compile_command_dump_toml(self, table, error)
7979
!> Error handling
8080
type(error_t), allocatable, intent(out) :: error
8181

82-
call self%destroy()
83-
84-
call set_string(table, "directory", self%directory, error, 'compile_command_t')
85-
if (allocated(error)) return
8682
call set_list(table, "arguments", self%arguments, error)
8783
if (allocated(error)) return
84+
call set_string(table, "directory", self%directory, error, 'compile_command_t')
85+
if (allocated(error)) return
8886
call set_string(table, "file", self%file, error, 'compile_command_t')
8987
if (allocated(error)) return
9088

@@ -102,12 +100,14 @@ subroutine compile_command_load_toml(self, table, error)
102100
!> Error handling
103101
type(error_t), allocatable, intent(out) :: error
104102

105-
call get_value(table, "directory", self%directory, error, 'compile_command_t')
106-
if (allocated(error)) return
103+
call self%destroy()
104+
107105
call get_list(table, "arguments", self%arguments, error)
108-
if (allocated(error)) return
109-
call get_value(table, "file", self%file, error, 'compile_command_t')
110-
if (allocated(error)) return
106+
if (allocated(error)) return
107+
108+
! Return unallocated value if not present
109+
call get_value(table, "directory", self%directory%s)
110+
call get_value(table, "file", self%file%s)
111111

112112
end subroutine compile_command_load_toml
113113

@@ -316,8 +316,6 @@ subroutine cct_dump_toml(self, table, error)
316316
integer :: stat, ii
317317
type(toml_array), pointer :: array
318318

319-
if (.not.allocated(self%command)) return
320-
321319
! Create array
322320
call add_array(table, 'compile_commands', array, stat=stat)
323321
if (stat/=toml_stat%success .or. .not.associated(array)) then
@@ -349,20 +347,22 @@ subroutine cct_load_toml(self, table, error)
349347
call self%destroy()
350348

351349
call get_value(table, key='compile_commands', ptr=array, requested=.true.,stat=stat)
352-
350+
353351
if (stat/=toml_stat%success .or. .not.associated(array)) then
354352

355353
call fatal_error(error, "TOML table has no 'compile_commands' key")
356354
return
357355

358356
else
359357

360-
n = len(array)
358+
n = len(array)
359+
if (n<=0) return
360+
361361
allocate(self%command(n))
362362

363363
do i = 1, n
364364
call get_value(array, pos=i, ptr=elem, stat=stat)
365-
if (stat /= toml_stat%success) then
365+
if (stat /= toml_stat%success .or. .not.associated(elem)) then
366366
call fatal_error(error, "Entry in 'compile_commands' field cannot be read")
367367
return
368368
end if

test/fpm_test/test_backend.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module test_backend
77
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, &
88
add_target, add_dependency
99
use fpm_backend, only: sort_target, schedule_targets
10+
use fpm_strings, only: string_t
1011
use fpm_compile_commands, only: compile_command_t, compile_command_table_t
1112
implicit none
1213
private

0 commit comments

Comments
 (0)