Skip to content

Commit 05eb31b

Browse files
committed
implement roundtrip serialization
1 parent d3854f2 commit 05eb31b

File tree

1 file changed

+62
-37
lines changed

1 file changed

+62
-37
lines changed

src/fpm_compile_commands.F90

Lines changed: 62 additions & 37 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
!># Store compiler commands in a `compile_commands.json` table
22
module fpm_compile_commands
33
use fpm_toml, only: serializable_t, set_string, set_list, get_value, get_list, toml_table, add_table, &
4-
toml_array, add_array, toml_stat
4+
toml_array, add_array, toml_stat, len
55
use jonquil, only: json_serialize, json_ser_config
66
use fpm_strings, only: string_t, operator(==)
77
use fpm_error, only: error_t, syntax_error, fatal_error
@@ -146,36 +146,7 @@ subroutine cct_dump_array(self, array, error)
146146
end do
147147

148148
end subroutine cct_dump_array
149-
150-
!> Dump compile_command_table_t to toml table
151-
subroutine cct_dump_toml(self, table, error)
152-
153-
!> Instance of the serializable object
154-
class(compile_command_table_t), intent(inout) :: self
155-
156-
!> Data structure
157-
type(toml_table), intent(inout) :: table
158-
159-
!> Error handling
160-
type(error_t), allocatable, intent(out) :: error
161-
162-
integer :: stat, ii
163-
type(toml_array), pointer :: array
164-
165-
if (.not.allocated(self%command)) return
166-
167-
! Create array
168-
call add_array(table, 'compile_commands', array, stat=stat)
169-
if (stat/=toml_stat%success .or. .not.associated(array)) then
170-
call fatal_error(error,"compile_command_table_t cannot create entry")
171-
return
172-
end if
173-
174-
! Dump to it
175-
call cct_dump_array(self, array, error)
176-
177-
end subroutine cct_dump_toml
178-
149+
179150
!> Write compile_commands.json file. Because Jonquil does not support non-named arrays,
180151
!> create a custom json here.
181152
subroutine cct_write(self, filename, error)
@@ -293,6 +264,35 @@ subroutine cct_register(self, command, error)
293264

294265
end subroutine cct_register
295266

267+
!> Dump compile_command_table_t to toml table
268+
subroutine cct_dump_toml(self, table, error)
269+
270+
!> Instance of the serializable object
271+
class(compile_command_table_t), intent(inout) :: self
272+
273+
!> Data structure
274+
type(toml_table), intent(inout) :: table
275+
276+
!> Error handling
277+
type(error_t), allocatable, intent(out) :: error
278+
279+
integer :: stat, ii
280+
type(toml_array), pointer :: array
281+
282+
if (.not.allocated(self%command)) return
283+
284+
! Create array
285+
call add_array(table, 'compile_commands', array, stat=stat)
286+
if (stat/=toml_stat%success .or. .not.associated(array)) then
287+
call fatal_error(error,"compile_command_table_t cannot create entry")
288+
return
289+
end if
290+
291+
! Dump to it
292+
call cct_dump_array(self, array, error)
293+
294+
end subroutine cct_dump_toml
295+
296296
!> Read compile_command_table_t from toml table (no checks made at this stage)
297297
subroutine cct_load_toml(self, table, error)
298298

@@ -305,12 +305,37 @@ subroutine cct_load_toml(self, table, error)
305305
!> Error handling
306306
type(error_t), allocatable, intent(out) :: error
307307

308-
! call get_value(table, "directory", self%directory, error, 'compile_command_table_t')
309-
! if (allocated(error)) return
310-
! call get_list(table, "arguments", self%arguments, error)
311-
! if (allocated(error)) return
312-
! call get_value(table, "file", self%file, error, 'compile_command_table_t')
313-
! if (allocated(error)) return
308+
integer :: stat, i, n
309+
type(toml_array), pointer :: array
310+
type(toml_table), pointer :: elem
311+
312+
call self%destroy()
313+
314+
call get_value(table, key='compile_commands', ptr=array, requested=.true.,stat=stat)
315+
316+
if (stat/=toml_stat%success .or. .not.associated(array)) then
317+
318+
call fatal_error(error, "TOML table has no 'compile_commands' key")
319+
return
320+
321+
else
322+
323+
n = len(array)
324+
allocate(self%command(n))
325+
326+
do i = 1, n
327+
call get_value(array, pos=i, ptr=elem, stat=stat)
328+
if (stat /= toml_stat%success) then
329+
call fatal_error(error, "Entry in 'compile_commands' field cannot be read")
330+
return
331+
end if
332+
333+
call self%command(i)%load(elem, error)
334+
if (allocated(error)) return
335+
336+
end do
337+
338+
end if
314339

315340
end subroutine cct_load_toml
316341

0 commit comments

Comments
 (0)