@@ -36,19 +36,19 @@ module fpm_toml
3636 contains
3737
3838 ! > Dump to TOML table, unit, file
39- procedure (to_toml), deferred, private :: dump_to_toml
39+ procedure (to_toml), deferred :: dump_to_toml
4040 procedure , non_overridable, private :: dump_to_file
4141 procedure , non_overridable, private :: dump_to_unit
4242 generic :: dump = > dump_to_toml, dump_to_file, dump_to_unit
4343
4444 ! > Load from TOML table, unit, file
45- procedure (from_toml), deferred, private :: load_from_toml
45+ procedure (from_toml), deferred :: load_from_toml
4646 procedure , non_overridable, private :: load_from_file
4747 procedure , non_overridable, private :: load_from_unit
4848 generic :: load = > load_from_toml, load_from_file, load_from_unit
4949
5050 ! > Serializable entities need a way to check that they're equal
51- procedure (is_equal), deferred, private :: serializable_is_same
51+ procedure (is_equal), deferred :: serializable_is_same
5252 generic :: operator (==) = > serializable_is_same
5353
5454 ! > Test load/write roundtrip
@@ -256,7 +256,7 @@ subroutine load_from_unit(self, unit, error, json)
256256 ! > Optional JSON format
257257 logical , optional , intent (in ) :: json
258258
259- type (toml_error), allocatable :: toml_error
259+ type (toml_error), allocatable :: local_error
260260 type (toml_table), allocatable :: table
261261 type (toml_table), pointer :: jtable
262262 class(toml_value), allocatable :: object
@@ -267,10 +267,10 @@ subroutine load_from_unit(self, unit, error, json)
267267 if (is_json) then
268268
269269 ! > init JSON interpreter
270- call json_load(object, unit, error= toml_error )
271- if (allocated (toml_error )) then
270+ call json_load(object, unit, error= local_error )
271+ if (allocated (local_error )) then
272272 allocate (error)
273- call move_alloc(toml_error % message, error% message)
273+ call move_alloc(local_error % message, error% message)
274274 return
275275 end if
276276
@@ -286,11 +286,11 @@ subroutine load_from_unit(self, unit, error, json)
286286 else
287287
288288 ! > use default TOML parser
289- call toml_load(table, unit, error= toml_error )
289+ call toml_load(table, unit, error= local_error )
290290
291- if (allocated (toml_error )) then
291+ if (allocated (local_error )) then
292292 allocate (error)
293- call move_alloc(toml_error % message, error% message)
293+ call move_alloc(local_error % message, error% message)
294294 return
295295 end if
296296
@@ -454,7 +454,7 @@ subroutine set_character(table, key, var, error, whereAt)
454454 character (len=* ), intent (in ) :: key
455455
456456 ! > The character variable
457- character (len= : ), allocatable , intent (in ) :: var
457+ character (len=* ), optional , intent (in ) :: var
458458
459459 ! > Error handling
460460 type (error_t), allocatable , intent (out ) :: error
@@ -471,7 +471,7 @@ subroutine set_character(table, key, var, error, whereAt)
471471 return
472472 end if
473473
474- if (allocated (var)) then
474+ if (present (var)) then
475475 call set_value(table, key, var, ierr)
476476 if (ierr/= toml_stat% success) then
477477 call fatal_error(error,' cannot set character key <' // key// ' > in TOML table' )
0 commit comments