Skip to content

Commit 1cfcaf8

Browse files
authored
Manifest: do not allow path lists in library.source-dir (#1077)
2 parents 1f08686 + 7ff83bc commit 1cfcaf8

File tree

3 files changed

+73
-3
lines changed

3 files changed

+73
-3
lines changed

src/fpm/manifest/library.f90

+6-1
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module fpm_manifest_library
1212
use fpm_error, only : error_t, syntax_error
1313
use fpm_strings, only: string_t, string_cat, operator(==)
1414
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+
set_list, set_string, get_value, has_list
1616
implicit none
1717
private
1818

@@ -63,6 +63,11 @@ subroutine new_library(self, table, error)
6363

6464
call check(table, error)
6565
if (allocated(error)) return
66+
67+
if (has_list(table, "source-dir")) then
68+
call syntax_error(error, "Manifest key [library.source-dir] does not allow list input")
69+
return
70+
end if
6671

6772
call get_value(table, "source-dir", self%source_dir, "src")
6873
call get_value(table, "build-script", self%build_script)

src/fpm/toml.f90

+24-1
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module fpm_toml
2828
public :: read_package_file, toml_table, toml_array, toml_key, toml_stat, &
2929
get_value, set_value, get_list, new_table, add_table, add_array, len, &
3030
toml_error, toml_serialize, toml_load, check_keys, set_list, set_string, &
31-
name_is_json
31+
name_is_json, has_list
3232

3333
!> An abstract interface for any fpm class that should be fully serializable to/from TOML/JSON
3434
type, abstract, public :: serializable_t
@@ -337,6 +337,29 @@ subroutine read_package_file(table, manifest, error)
337337
end if
338338

339339
end subroutine read_package_file
340+
341+
!> Check if an instance of the TOML data structure contains a list
342+
logical function has_list(table, key)
343+
344+
!> Instance of the TOML data structure
345+
type(toml_table), intent(inout) :: table
346+
347+
!> Key to read from
348+
character(len=*), intent(in) :: key
349+
350+
type(toml_array), pointer :: children
351+
352+
has_list = .false.
353+
354+
if (.not.table%has_key(key)) return
355+
356+
call get_value(table, key, children, requested=.false.)
357+
358+
! There is an allocated list
359+
has_list = associated(children)
360+
361+
end function has_list
362+
340363

341364
subroutine get_list(table, key, list, error)
342365

test/fpm_test/test_manifest.f90

+43-1
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module test_manifest
44
use testsuite, only : new_unittest, unittest_t, error_t, test_failed, check_string
55
use fpm_manifest
66
use fpm_manifest_profile, only: profile_config_t, find_profile
7-
use fpm_strings, only: operator(.in.)
7+
use fpm_strings, only: operator(.in.), string_t
88
use fpm_error, only: fatal_error, error_t
99
implicit none
1010
private
@@ -46,6 +46,7 @@ subroutine collect_manifest(tests)
4646
& new_unittest("build-key-invalid", test_build_invalid_key), &
4747
& new_unittest("library-empty", test_library_empty), &
4848
& new_unittest("library-wrongkey", test_library_wrongkey, should_fail=.true.), &
49+
& new_unittest("library-list", test_library_list, should_fail=.true.), &
4950
& new_unittest("package-simple", test_package_simple), &
5051
& new_unittest("package-empty", test_package_empty, should_fail=.true.), &
5152
& new_unittest("package-typeerror", test_package_typeerror, should_fail=.true.), &
@@ -887,6 +888,47 @@ subroutine test_library_wrongkey(error)
887888

888889
end subroutine test_library_wrongkey
889890

891+
!> Pass a TOML table with not allowed source dirs
892+
subroutine test_library_list(error)
893+
use fpm_manifest_library
894+
use fpm_toml, only : new_table, set_list, toml_table
895+
896+
!> Error handling
897+
type(error_t), allocatable, intent(out) :: error
898+
899+
type(string_t), allocatable :: source_dirs(:)
900+
type(toml_table) :: table
901+
type(library_config_t) :: library
902+
903+
source_dirs = [string_t("src1"),string_t("src2")]
904+
call new_table (table)
905+
call set_list (table, "source-dir", source_dirs, error)
906+
call new_library(library, table, error)
907+
908+
end subroutine test_library_list
909+
910+
!> Pass a TOML table with a 1-sized source dir list
911+
subroutine test_library_listone(error)
912+
use fpm_manifest_library
913+
use fpm_toml, only : new_table, set_list, toml_table
914+
915+
!> Error handling
916+
type(error_t), allocatable, intent(out) :: error
917+
918+
type(package_config_t) :: package
919+
character(:), allocatable :: temp_file
920+
integer :: unit
921+
922+
open(file=temp_file, newunit=unit)
923+
write(unit, '(a)') &
924+
& 'name = "example"', &
925+
& '[library]', &
926+
& 'source-dir = ["my-src"]'
927+
close(unit)
928+
929+
call get_package_data(package, temp_file, error)
930+
931+
end subroutine test_library_listone
890932

891933
!> Packages cannot be created from empty tables
892934
subroutine test_package_simple(error)

0 commit comments

Comments
 (0)