10
10
! >```
11
11
module fpm_manifest_library
12
12
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
15
16
implicit none
16
17
private
17
18
18
19
public :: library_config_t, new_library
19
20
20
21
21
22
! > Configuration meta data for a library
22
- type :: library_config_t
23
+ type, extends(serializable_t) :: library_config_t
23
24
24
25
! > Source path prefix
25
26
character (len= :), allocatable :: source_dir
@@ -35,8 +36,15 @@ module fpm_manifest_library
35
36
! > Print information on this instance
36
37
procedure :: info
37
38
39
+ ! > Serialization interface
40
+ procedure :: serializable_is_same = > library_is_same
41
+ procedure :: dump_to_toml
42
+ procedure :: load_from_toml
43
+
38
44
end type library_config_t
39
45
46
+ character (* ), parameter , private :: class_name = ' library_config_t'
47
+
40
48
41
49
contains
42
50
@@ -138,5 +146,69 @@ subroutine info(self, unit, verbosity)
138
146
139
147
end subroutine info
140
148
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
+
141
213
142
214
end module fpm_manifest_library
0 commit comments