Skip to content

Commit e6c5e6a

Browse files
authored
Merge pull request #171 from awvwgk/manifest-testing
Increase test coverage of fpm manifest
2 parents e02171d + e6a10de commit e6c5e6a

File tree

9 files changed

+519
-54
lines changed

9 files changed

+519
-54
lines changed

fpm/fpm.toml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ copyright = "2020 fpm contributors"
88
[dependencies]
99
[dependencies.toml-f]
1010
git = "https://github.com/toml-f/toml-f"
11-
rev = "290ba87671ab593e7bd51599e1d80ea736b3cd36"
11+
tag = "v0.2"
1212

1313
[[test]]
1414
name = "fpm-test"

fpm/src/fpm/manifest/dependency.f90

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ subroutine new_dependency(self, table, error)
9494
end if
9595

9696
if (.not.allocated(self%git)) then
97-
call get_value(table, "revision", obj)
97+
call get_value(table, "rev", obj)
9898
if (allocated(obj)) then
9999
self%git = git_target_revision(url, obj)
100100
end if
@@ -120,9 +120,10 @@ subroutine check(table, error)
120120

121121
character(len=:), allocatable :: name
122122
type(toml_key), allocatable :: list(:)
123-
logical :: url_present, git_target_present
123+
logical :: url_present, git_target_present, has_path
124124
integer :: ikey
125125

126+
has_path = .false.
126127
url_present = .false.
127128
git_target_present = .false.
128129

@@ -146,6 +147,7 @@ subroutine check(table, error)
146147
exit
147148
end if
148149
url_present = .true.
150+
has_path = list(ikey)%key == 'path'
149151

150152
case("branch", "rev", "tag")
151153
if (git_target_present) then
@@ -163,7 +165,7 @@ subroutine check(table, error)
163165
return
164166
end if
165167

166-
if (.not.url_present .and. git_target_present) then
168+
if (has_path .and. git_target_present) then
167169
call syntax_error(error, "Dependency "//name//" uses a local path, therefore no git identifiers are allowed")
168170
end if
169171

@@ -182,7 +184,7 @@ subroutine new_dependencies(deps, table, error)
182184
!> Error handling
183185
type(error_t), allocatable, intent(out) :: error
184186

185-
class(toml_table), pointer :: node
187+
type(toml_table), pointer :: node
186188
type(toml_key), allocatable :: list(:)
187189
integer :: idep, stat
188190

fpm/src/fpm/manifest/executable.f90

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ subroutine new_executable(self, table, error)
5757
!> Error handling
5858
type(error_t), allocatable, intent(out) :: error
5959

60-
class(toml_table), pointer :: child
60+
type(toml_table), pointer :: child
6161

6262
call check(table, error)
6363
if (allocated(error)) return
@@ -104,7 +104,7 @@ subroutine check(table, error)
104104
do ikey = 1, size(list)
105105
select case(list(ikey)%key)
106106
case default
107-
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed executable entry")
107+
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed as executable entry")
108108
exit
109109

110110
case("name")
@@ -115,6 +115,7 @@ subroutine check(table, error)
115115

116116
end select
117117
end do
118+
if (allocated(error)) return
118119

119120
if (.not.name_present) then
120121
call syntax_error(error, "Executable name is not provided, please add a name entry")

fpm/src/fpm/manifest/library.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ subroutine check(table, error)
7777
do ikey = 1, size(list)
7878
select case(list(ikey)%key)
7979
case default
80-
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in package file")
80+
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in library")
8181
exit
8282

8383
case("source-dir", "build-script")

fpm/src/fpm/manifest/package.f90

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -85,8 +85,8 @@ subroutine new_package(self, table, error)
8585
!> Error handling
8686
type(error_t), allocatable, intent(out) :: error
8787

88-
class(toml_table), pointer :: child, node
89-
class(toml_array), pointer :: children
88+
type(toml_table), pointer :: child, node
89+
type(toml_array), pointer :: children
9090
integer :: ii, nn, stat
9191

9292
call check(table, error)
@@ -184,6 +184,7 @@ subroutine check(table, error)
184184
name_present = .true.
185185

186186
case("version", "license", "author", "maintainer", "copyright", &
187+
& "description", "keywords", "categories", "homepage", &
187188
& "dependencies", "dev-dependencies", "test", "executable", &
188189
& "library")
189190
continue

fpm/src/fpm/manifest/test.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ subroutine new_test(self, table, error)
5050
!> Error handling
5151
type(error_t), allocatable, intent(out) :: error
5252

53-
class(toml_table), pointer :: child
53+
type(toml_table), pointer :: child
5454

5555
call check(table, error)
5656
if (allocated(error)) return
@@ -108,6 +108,7 @@ subroutine check(table, error)
108108

109109
end select
110110
end do
111+
if (allocated(error)) return
111112

112113
if (.not.name_present) then
113114
call syntax_error(error, "Test name is not provided, please add a name entry")

fpm/src/fpm/toml.f90

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -14,14 +14,13 @@
1414
module fpm_toml
1515
use fpm_error, only : error_t, fatal_error, file_not_found_error
1616
use tomlf, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
17-
& toml_parse, toml_error
18-
use tomlf_type, only : new_table, len
17+
& set_value, toml_parse, toml_error, new_table, add_table, add_array, len
1918
implicit none
2019
private
2120

2221
public :: read_package_file
23-
public :: toml_table, toml_array, toml_key, toml_stat, get_value
24-
public :: new_table, len
22+
public :: toml_table, toml_array, toml_key, toml_stat, get_value, set_value
23+
public :: new_table, add_table, add_array, len
2524

2625

2726
contains

0 commit comments

Comments
 (0)