diff --git a/src/fpm/manifest/library.f90 b/src/fpm/manifest/library.f90 index 52e33efecb..9cb6c71715 100644 --- a/src/fpm/manifest/library.f90 +++ b/src/fpm/manifest/library.f90 @@ -60,11 +60,28 @@ subroutine new_library(self, table, error) !> Error handling type(error_t), allocatable, intent(out) :: error + + type(string_t), allocatable :: source_dirs(:) call check(table, error) if (allocated(error)) return - - call get_value(table, "source-dir", self%source_dir, "src") + + ! Source dir: attempt list source-dir=["src"] + call get_list(table, "source-dir", source_dirs, error) + if (allocated(error)) return + + if (allocated(source_dirs)) then + if (size(source_dirs)==1) then + call move_alloc(from=source_dirs(1)%s,to=self%source_dir) + deallocate(source_dirs) + else + call syntax_error(error, "Manifest key [library.source-dir] does not allow lists") + return + end if + else + call get_value(table, "source-dir", self%source_dir, "src") + end if + call get_value(table, "build-script", self%build_script) call get_list(table, "include-dir", self%include_dir, error) diff --git a/test/fpm_test/test_manifest.f90 b/test/fpm_test/test_manifest.f90 index 316508d9bc..120c3ef23d 100644 --- a/test/fpm_test/test_manifest.f90 +++ b/test/fpm_test/test_manifest.f90 @@ -4,7 +4,7 @@ module test_manifest use testsuite, only : new_unittest, unittest_t, error_t, test_failed, check_string use fpm_manifest use fpm_manifest_profile, only: profile_config_t, find_profile - use fpm_strings, only: operator(.in.) + use fpm_strings, only: operator(.in.),string_t use fpm_error, only: fatal_error, error_t implicit none private @@ -46,6 +46,8 @@ subroutine collect_manifest(tests) & new_unittest("build-key-invalid", test_build_invalid_key), & & new_unittest("library-empty", test_library_empty), & & new_unittest("library-wrongkey", test_library_wrongkey, should_fail=.true.), & + & new_unittest("library-wrongpath", test_library_wrongpath, should_fail=.true.), & + & new_unittest("library-onepath", test_library_onepath), & & new_unittest("package-simple", test_package_simple), & & new_unittest("package-empty", test_package_empty, should_fail=.true.), & & new_unittest("package-typeerror", test_package_typeerror, should_fail=.true.), & @@ -887,6 +889,43 @@ subroutine test_library_wrongkey(error) end subroutine test_library_wrongkey + !> Pass a TOML table with not allowed source dirs + subroutine test_library_wrongpath(error) + use fpm_manifest_library + use fpm_toml, only : new_table, set_list, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(string_t), allocatable :: source_dirs(:) + type(toml_table) :: table + type(library_config_t) :: library + + source_dirs = [string_t("src1"),string_t("src2")] + call new_table (table) + call set_list (table, "source-dir", source_dirs, error) + call new_library(library, table, error) + + end subroutine test_library_wrongpath + + !> Pass a TOML table with a 1-sized source dir list + subroutine test_library_onepath(error) + use fpm_manifest_library + use fpm_toml, only : new_table, set_list, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(string_t), allocatable :: source_dirs(:) + type(toml_table) :: table + type(library_config_t) :: library + + source_dirs = [string_t("src1")] + call new_table (table) + call set_list (table, "source-dir", source_dirs, error) + call new_library(library, table, error) + + end subroutine test_library_onepath !> Packages cannot be created from empty tables subroutine test_package_simple(error)