Skip to content

Commit

Permalink
Improve error handling for invalid git dependencies (#797)
Browse files Browse the repository at this point in the history
  • Loading branch information
minhqdao authored Nov 29, 2022
1 parent 9640770 commit b0f55f0
Show file tree
Hide file tree
Showing 2 changed files with 39 additions and 3 deletions.
18 changes: 15 additions & 3 deletions src/fpm/manifest/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@ subroutine check(table, error)
!> Error handling
type(error_t), allocatable, intent(out) :: error

character(len=:), allocatable :: name
character(len=:), allocatable :: name, url
type(toml_key), allocatable :: list(:)
logical :: url_present, git_target_present, has_path
integer :: ikey
Expand All @@ -148,13 +148,25 @@ subroutine check(table, error)
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in dependency "//name)
exit

case("git", "path")
case("git")
if (url_present) then
call syntax_error(error, "Dependency "//name//" cannot have both git and path entries")
exit
end if
call get_value(table, "git", url)
if (.not.allocated(url)) then
call syntax_error(error, "Dependency "//name//" has invalid git source")
exit
end if
url_present = .true.

case("path")
if (url_present) then
call syntax_error(error, "Dependency "//name//" cannot have both git and path entries")
exit
end if
url_present = .true.
has_path = list(ikey)%key == 'path'
has_path = .true.

case("branch", "rev", "tag")
if (git_target_present) then
Expand Down
24 changes: 24 additions & 0 deletions test/fpm_test/test_manifest.f90
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@ subroutine collect_manifest(testsuite)
& new_unittest("dependency-gitpath", test_dependency_gitpath, should_fail=.true.), &
& new_unittest("dependency-nourl", test_dependency_nourl, should_fail=.true.), &
& new_unittest("dependency-gitconflict", test_dependency_gitconflict, should_fail=.true.), &
& new_unittest("dependency-invalid-git", test_dependency_invalid_git, should_fail=.true.), &
& new_unittest("dependency-wrongkey", test_dependency_wrongkey, should_fail=.true.), &
& new_unittest("dependencies-empty", test_dependencies_empty), &
& new_unittest("dependencies-typeerror", test_dependencies_typeerror, should_fail=.true.), &
Expand Down Expand Up @@ -350,6 +351,29 @@ subroutine test_dependency_gitconflict(error)
end subroutine test_dependency_gitconflict


!> Try to create a git dependency with invalid source format
subroutine test_dependency_invalid_git(error)
use fpm_manifest_dependency
use fpm_toml, only : new_table, add_table, toml_table, set_value

!> Error handling
type(error_t), allocatable, intent(out) :: error

type(toml_table) :: table
type(toml_table), pointer :: child
integer :: stat
type(dependency_config_t) :: dependency

call new_table(table)
table%key = 'example'
call add_table(table, 'git', child)
call set_value(child, 'path', '../../package')

call new_dependency(dependency, table, error=error)

end subroutine test_dependency_invalid_git


!> Try to create a dependency with conflicting entries
subroutine test_dependency_wrongkey(error)
use fpm_manifest_dependency
Expand Down

0 comments on commit b0f55f0

Please sign in to comment.