Skip to content

Commit 567d719

Browse files
committed
add tests
1 parent 54698d9 commit 567d719

File tree

1 file changed

+44
-1
lines changed

1 file changed

+44
-1
lines changed

test/fpm_test/test_manifest.f90

Lines changed: 44 additions & 1 deletion
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,8 @@ 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.), &
50+
& new_unittest("library-list-one", test_library_listone, should_fail=.true.), &
4951
& new_unittest("package-simple", test_package_simple), &
5052
& new_unittest("package-empty", test_package_empty, should_fail=.true.), &
5153
& new_unittest("package-typeerror", test_package_typeerror, should_fail=.true.), &
@@ -887,6 +889,47 @@ subroutine test_library_wrongkey(error)
887889

888890
end subroutine test_library_wrongkey
889891

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

891934
!> Packages cannot be created from empty tables
892935
subroutine test_package_simple(error)

0 commit comments

Comments
 (0)