diff options
-rw-r--r-- | fpm/src/fpm/error.f90 | 7 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/dependency.f90 | 9 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/executable.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/library.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/package.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm/manifest/test.f90 | 6 | ||||
-rw-r--r-- | fpm/src/fpm/toml.f90 | 5 | ||||
-rw-r--r-- | fpm/test/test_manifest.f90 | 136 | ||||
-rw-r--r-- | fpm/test/test_toml.f90 | 18 |
9 files changed, 170 insertions, 17 deletions
diff --git a/fpm/src/fpm/error.f90 b/fpm/src/fpm/error.f90 index 957d3bf..aebd7e4 100644 --- a/fpm/src/fpm/error.f90 +++ b/fpm/src/fpm/error.f90 @@ -49,11 +49,8 @@ contains !> Name of the missing file character(len=*), intent(in) :: file_name - character(len=:), allocatable :: message - - message = "'"//file_name//"' could not be found, check if the file exists" - - call move_alloc(message, error%message) + allocate(error) + error%message = "'"//file_name//"' could not be found, check if the file exists" end subroutine file_not_found_error diff --git a/fpm/src/fpm/manifest/dependency.f90 b/fpm/src/fpm/manifest/dependency.f90 index 1ee61b7..8a3d879 100644 --- a/fpm/src/fpm/manifest/dependency.f90 +++ b/fpm/src/fpm/manifest/dependency.f90 @@ -129,7 +129,7 @@ contains call table%get_key(name) call table%get_keys(list) - if (.not.allocated(list)) then + if (size(list) < 1) then call syntax_error(error, "Dependency "//name//" does not provide sufficient entries") return end if @@ -158,6 +158,11 @@ contains end do if (allocated(error)) return + if (.not.url_present) then + call syntax_error(error, "Dependency "//name//" does not provide a method to actually retrieve itself") + return + end if + if (.not.url_present .and. git_target_present) then call syntax_error(error, "Dependency "//name//" uses a local path, therefore no git identifiers are allowed") end if @@ -183,7 +188,7 @@ contains call table%get_keys(list) ! An empty table is okay - if (.not.allocated(list)) return + if (size(list) < 1) return allocate(deps(size(list))) do idep = 1, size(list) diff --git a/fpm/src/fpm/manifest/executable.f90 b/fpm/src/fpm/manifest/executable.f90 index 94d4000..f706001 100644 --- a/fpm/src/fpm/manifest/executable.f90 +++ b/fpm/src/fpm/manifest/executable.f90 @@ -96,7 +96,7 @@ contains call table%get_keys(list) - if (.not.allocated(list)) then + if (size(list) < 1) then call syntax_error(error, "Executable section does not provide sufficient entries") return end if diff --git a/fpm/src/fpm/manifest/library.f90 b/fpm/src/fpm/manifest/library.f90 index a297c2f..40e5e92 100644 --- a/fpm/src/fpm/manifest/library.f90 +++ b/fpm/src/fpm/manifest/library.f90 @@ -72,7 +72,7 @@ contains call table%get_keys(list) ! table can be empty - if (.not.allocated(list)) return + if (size(list) < 1) return do ikey = 1, size(list) select case(list(ikey)%key) diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index 95194d2..4c2c14a 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -169,7 +169,7 @@ contains call table%get_keys(list) - if (.not.allocated(list)) then + if (size(list) < 1) then call syntax_error(error, "Package file is empty") return end if diff --git a/fpm/src/fpm/manifest/test.f90 b/fpm/src/fpm/manifest/test.f90 index c35ea63..a6c6f64 100644 --- a/fpm/src/fpm/manifest/test.f90 +++ b/fpm/src/fpm/manifest/test.f90 @@ -89,8 +89,8 @@ contains call table%get_keys(list) - if (.not.allocated(list)) then - call syntax_error(error, "Executable section does not provide sufficient entries") + if (size(list) < 1) then + call syntax_error(error, "Test section does not provide sufficient entries") return end if @@ -110,7 +110,7 @@ contains end do if (.not.name_present) then - call syntax_error(error, "Executable name is not provided, please add a name entry") + call syntax_error(error, "Test name is not provided, please add a name entry") end if end subroutine check diff --git a/fpm/src/fpm/toml.f90 b/fpm/src/fpm/toml.f90 index d95a093..183278d 100644 --- a/fpm/src/fpm/toml.f90 +++ b/fpm/src/fpm/toml.f90 @@ -15,12 +15,13 @@ module fpm_toml use fpm_error, only : error_t, fatal_error, file_not_found_error use tomlf, only : toml_table, toml_array, toml_key, toml_stat, get_value, & & toml_parse, toml_error - use tomlf_type, only : len + use tomlf_type, only : new_table, len implicit none private public :: read_package_file - public :: toml_table, toml_array, toml_key, toml_stat, get_value, len + public :: toml_table, toml_array, toml_key, toml_stat, get_value + public :: new_table, len contains diff --git a/fpm/test/test_manifest.f90 b/fpm/test/test_manifest.f90 index 08236d5..117ea3a 100644 --- a/fpm/test/test_manifest.f90 +++ b/fpm/test/test_manifest.f90 @@ -21,7 +21,13 @@ contains & new_unittest("valid-manifest", test_valid_manifest), & & new_unittest("invalid-manifest", test_invalid_manifest, should_fail=.true.), & & new_unittest("default-library", test_default_library), & - & new_unittest("default-executable", test_default_executable)] + & new_unittest("default-executable", test_default_executable), & + & new_unittest("dependency-empty", test_dependency_empty, should_fail=.true.), & + & new_unittest("dependencies-empty", test_dependencies_empty), & + & new_unittest("executable-empty", test_executable_empty, should_fail=.true.), & + & new_unittest("library-empty", test_library_empty), & + & new_unittest("package-empty", test_package_empty, should_fail=.true.), & + & new_unittest("test-empty", test_test_empty, should_fail=.true.)] end subroutine collect_manifest @@ -185,4 +191,132 @@ contains end subroutine test_default_executable + !> Dependencies cannot be created from empty tables + subroutine test_dependency_empty(error) + use fpm_manifest_dependency + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(dependency_t) :: dependency + + call new_table(table) + table%key = "example" + + call new_dependency(dependency, table, error) + + call dependency%info(0) + + end subroutine test_dependency_empty + + + !> Dependency tables can be empty + subroutine test_dependencies_empty(error) + use fpm_manifest_dependency + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(dependency_t), allocatable :: dependencies(:) + + call new_table(table) + + call new_dependencies(dependencies, table, error) + if (allocated(error)) return + + if (allocated(dependencies)) then + call test_failed(error, "Found dependencies in empty table") + end if + + end subroutine test_dependencies_empty + + + !> Executables cannot be created from empty tables + subroutine test_executable_empty(error) + use fpm_manifest_executable + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(executable_t) :: executable + + call new_table(table) + + call new_executable(executable, table, error) + + end subroutine test_executable_empty + + + !> Libraries can be created from empty tables + subroutine test_library_empty(error) + use fpm_manifest_library + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(library_t) :: library + + call new_table(table) + + call new_library(library, table, error) + if (allocated(error)) return + + if (.not.allocated(library%source_dir)) then + call test_failed(error, "Default library source-dir is not set") + return + end if + + if (library%source_dir /= "src") then + call test_failed(error, "Default library source-dir is "// & + & library%source_dir//" but should be src") + return + end if + + end subroutine test_library_empty + + + !> Packages cannot be created from empty tables + subroutine test_package_empty(error) + use fpm_manifest_package + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(package_t) :: package + + call new_table(table) + + call new_package(package, table, error) + + end subroutine test_package_empty + + + !> Tests cannot be created from empty tables + subroutine test_test_empty(error) + use fpm_manifest_test + use fpm_toml, only : new_table, toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(test_t) :: test + + call new_table(table) + + call new_test(test, table, error) + + end subroutine test_test_empty + + end module test_manifest diff --git a/fpm/test/test_toml.f90 b/fpm/test/test_toml.f90 index d30ef0d..0a5abd6 100644 --- a/fpm/test/test_toml.f90 +++ b/fpm/test/test_toml.f90 @@ -19,7 +19,8 @@ contains testsuite = [ & & new_unittest("valid-toml", test_valid_toml), & - & new_unittest("invalid-toml", test_invalid_toml, should_fail=.true.)] + & new_unittest("invalid-toml", test_invalid_toml, should_fail=.true.), & + & new_unittest("missing-file", test_missing_file, should_fail=.true.)] end subroutine collect_toml @@ -92,4 +93,19 @@ contains end subroutine test_invalid_toml + !> Try to read configuration from a non-existing file + subroutine test_missing_file(error) + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table), allocatable :: table + character(len=:), allocatable :: string + integer :: unit + + call read_package_file(table, 'low+chance+of+existing.toml', error) + + end subroutine test_missing_file + + end module test_toml |