Skip to content

Commit 569f898

Browse files
committed
serialize library_config_t
1 parent 95cd89f commit 569f898

File tree

2 files changed

+100
-5
lines changed

2 files changed

+100
-5
lines changed

src/fpm/manifest/library.f90

Lines changed: 75 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -10,16 +10,17 @@
1010
!>```
1111
module fpm_manifest_library
1212
use fpm_error, only : error_t, syntax_error
13-
use fpm_strings, only: string_t, string_cat
14-
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list
13+
use fpm_strings, only: string_t, string_cat, operator(==)
14+
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value, get_list, serializable_t, set_value, &
15+
set_list, set_string, get_value, get_list
1516
implicit none
1617
private
1718

1819
public :: library_config_t, new_library
1920

2021

2122
!> Configuration meta data for a library
22-
type :: library_config_t
23+
type, extends(serializable_t) :: library_config_t
2324

2425
!> Source path prefix
2526
character(len=:), allocatable :: source_dir
@@ -35,8 +36,15 @@ module fpm_manifest_library
3536
!> Print information on this instance
3637
procedure :: info
3738

39+
!> Serialization interface
40+
procedure :: serializable_is_same => library_is_same
41+
procedure :: dump_to_toml
42+
procedure :: load_from_toml
43+
3844
end type library_config_t
3945

46+
character(*), parameter, private :: class_name = 'library_config_t'
47+
4048

4149
contains
4250

@@ -138,5 +146,69 @@ subroutine info(self, unit, verbosity)
138146

139147
end subroutine info
140148

149+
logical function library_is_same(this,that)
150+
class(library_config_t), intent(in) :: this
151+
class(serializable_t), intent(in) :: that
152+
153+
library_is_same = .false.
154+
155+
select type (other=>that)
156+
type is (library_config_t)
157+
if (.not.this%include_dir==other%include_dir) return
158+
if (.not.allocated(this%source_dir).eqv.allocated(other%source_dir)) return
159+
if (.not.this%source_dir==other%source_dir) return
160+
if (.not.allocated(this%build_script).eqv.allocated(other%build_script)) return
161+
if (.not.this%build_script==other%build_script) return
162+
class default
163+
! Not the same type
164+
return
165+
end select
166+
167+
!> All checks passed!
168+
library_is_same = .true.
169+
170+
end function library_is_same
171+
172+
!> Dump install config to toml table
173+
subroutine dump_to_toml(self, table, error)
174+
175+
!> Instance of the serializable object
176+
class(library_config_t), intent(inout) :: self
177+
178+
!> Data structure
179+
type(toml_table), intent(inout) :: table
180+
181+
!> Error handling
182+
type(error_t), allocatable, intent(out) :: error
183+
184+
call set_string(table, "source-dir", self%source_dir, error, class_name)
185+
if (allocated(error)) return
186+
call set_string(table, "build-script", self%build_script, error, class_name)
187+
if (allocated(error)) return
188+
call set_list(table, "include-dir", self%include_dir, error)
189+
if (allocated(error)) return
190+
191+
end subroutine dump_to_toml
192+
193+
!> Read install config from toml table (no checks made at this stage)
194+
subroutine load_from_toml(self, table, error)
195+
196+
!> Instance of the serializable object
197+
class(library_config_t), intent(inout) :: self
198+
199+
!> Data structure
200+
type(toml_table), intent(inout) :: table
201+
202+
!> Error handling
203+
type(error_t), allocatable, intent(out) :: error
204+
205+
call get_value(table, "source-dir", self%source_dir)
206+
if (allocated(error)) return
207+
call get_value(table, "build-script", self%build_script)
208+
if (allocated(error)) return
209+
call get_list(table, "include-dir", self%include_dir, error)
210+
211+
end subroutine load_from_toml
212+
141213

142214
end module fpm_manifest_library

test/fpm_test/test_toml.f90

Lines changed: 25 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module test_toml
99
use fpm_manifest_dependency, only: dependency_config_t, dependency_destroy
1010
use fpm_manifest_install
1111
use fpm_manifest_fortran
12+
use fpm_manifest_library
1213
use fpm_versioning, only: new_version
1314
use fpm_strings, only: string_t, operator(==), split
1415
use fpm_model, only: fortran_features_t, package_t, FPM_SCOPE_LIB, FPM_UNIT_MODULE, fpm_model_t, &
@@ -47,6 +48,7 @@ subroutine collect_toml(testsuite)
4748
& new_unittest("serialize-dependency-tree-invalid2", dependency_tree_invalid2, should_fail=.true.), &
4849
& new_unittest("serialize-install-config", install_config_roundtrip), &
4950
& new_unittest("serialize-fortran-config", fortran_features_roundtrip), &
51+
& new_unittest("serialize-library-config", library_config_roundtrip), &
5052
& new_unittest("serialize-string-array", string_array_roundtrip), &
5153
& new_unittest("serialize-fortran-features", fft_roundtrip), &
5254
& new_unittest("serialize-fortran-invalid", fft_invalid, should_fail=.true.), &
@@ -1175,8 +1177,6 @@ subroutine fortran_features_roundtrip(error)
11751177

11761178
type(fortran_config_t) :: fortran
11771179

1178-
integer :: loop
1179-
11801180
fortran%implicit_external = .true.
11811181
fortran%implicit_typing = .false.
11821182
fortran%source_form = 'free'
@@ -1189,4 +1189,27 @@ subroutine fortran_features_roundtrip(error)
11891189

11901190
end subroutine fortran_features_roundtrip
11911191

1192+
subroutine library_config_roundtrip(error)
1193+
1194+
!> Error handling
1195+
type(error_t), allocatable, intent(out) :: error
1196+
1197+
type(library_config_t) :: lib
1198+
1199+
lib%source_dir = 'lib'
1200+
lib%include_dir = [string_t('a'),string_t('b')]
1201+
1202+
call lib%test_serialization('library_config: 1',error)
1203+
if (allocated(error)) return
1204+
1205+
lib%build_script = 'install.sh'
1206+
1207+
call lib%test_serialization('library_config: 2',error)
1208+
if (allocated(error)) return
1209+
1210+
deallocate(lib%include_dir)
1211+
call lib%test_serialization('library_config: 3',error)
1212+
1213+
end subroutine library_config_roundtrip
1214+
11921215
end module test_toml

0 commit comments

Comments
 (0)