Skip to content

Commit b0f55f0

Browse files
authored
Improve error handling for invalid git dependencies (#797)
1 parent 9640770 commit b0f55f0

File tree

2 files changed

+39
-3
lines changed

2 files changed

+39
-3
lines changed

src/fpm/manifest/dependency.f90

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -125,7 +125,7 @@ subroutine check(table, error)
125125
!> Error handling
126126
type(error_t), allocatable, intent(out) :: error
127127

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

151-
case("git", "path")
151+
case("git")
152+
if (url_present) then
153+
call syntax_error(error, "Dependency "//name//" cannot have both git and path entries")
154+
exit
155+
end if
156+
call get_value(table, "git", url)
157+
if (.not.allocated(url)) then
158+
call syntax_error(error, "Dependency "//name//" has invalid git source")
159+
exit
160+
end if
161+
url_present = .true.
162+
163+
case("path")
152164
if (url_present) then
153165
call syntax_error(error, "Dependency "//name//" cannot have both git and path entries")
154166
exit
155167
end if
156168
url_present = .true.
157-
has_path = list(ikey)%key == 'path'
169+
has_path = .true.
158170

159171
case("branch", "rev", "tag")
160172
if (git_target_present) then

test/fpm_test/test_manifest.f90

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ subroutine collect_manifest(testsuite)
3131
& new_unittest("dependency-gitpath", test_dependency_gitpath, should_fail=.true.), &
3232
& new_unittest("dependency-nourl", test_dependency_nourl, should_fail=.true.), &
3333
& new_unittest("dependency-gitconflict", test_dependency_gitconflict, should_fail=.true.), &
34+
& new_unittest("dependency-invalid-git", test_dependency_invalid_git, should_fail=.true.), &
3435
& new_unittest("dependency-wrongkey", test_dependency_wrongkey, should_fail=.true.), &
3536
& new_unittest("dependencies-empty", test_dependencies_empty), &
3637
& new_unittest("dependencies-typeerror", test_dependencies_typeerror, should_fail=.true.), &
@@ -350,6 +351,29 @@ subroutine test_dependency_gitconflict(error)
350351
end subroutine test_dependency_gitconflict
351352

352353

354+
!> Try to create a git dependency with invalid source format
355+
subroutine test_dependency_invalid_git(error)
356+
use fpm_manifest_dependency
357+
use fpm_toml, only : new_table, add_table, toml_table, set_value
358+
359+
!> Error handling
360+
type(error_t), allocatable, intent(out) :: error
361+
362+
type(toml_table) :: table
363+
type(toml_table), pointer :: child
364+
integer :: stat
365+
type(dependency_config_t) :: dependency
366+
367+
call new_table(table)
368+
table%key = 'example'
369+
call add_table(table, 'git', child)
370+
call set_value(child, 'path', '../../package')
371+
372+
call new_dependency(dependency, table, error=error)
373+
374+
end subroutine test_dependency_invalid_git
375+
376+
353377
!> Try to create a dependency with conflicting entries
354378
subroutine test_dependency_wrongkey(error)
355379
use fpm_manifest_dependency

0 commit comments

Comments
 (0)