@@ -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