Skip to content

Commit

Permalink
add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Sep 19, 2024
1 parent 88a84d3 commit f4cf9d3
Showing 1 changed file with 40 additions and 1 deletion.
41 changes: 40 additions & 1 deletion test/fpm_test/test_manifest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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.), &
Expand Down Expand Up @@ -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)
Expand Down

0 comments on commit f4cf9d3

Please sign in to comment.