Skip to content

Commit fc4ac0e

Browse files
authored
Improve error message for [build] structure errors (#890)
2 parents b03a676 + dfafcf3 commit fc4ac0e

File tree

3 files changed

+66
-10
lines changed

3 files changed

+66
-10
lines changed

src/fpm/manifest/build.f90

Lines changed: 12 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -52,20 +52,23 @@ module fpm_manifest_build
5252

5353

5454
!> Construct a new build configuration from a TOML data structure
55-
subroutine new_build_config(self, table, error)
55+
subroutine new_build_config(self, table, package_name, error)
5656

5757
!> Instance of the build configuration
5858
type(build_config_t), intent(out) :: self
5959

6060
!> Instance of the TOML data structure
6161
type(toml_table), intent(inout) :: table
6262

63+
!> Package name
64+
character(len=*), intent(in) :: package_name
65+
6366
!> Error handling
6467
type(error_t), allocatable, intent(out) :: error
6568

6669
integer :: stat
6770

68-
call check(table, error)
71+
call check(table, package_name, error)
6972
if (allocated(error)) return
7073

7174
call get_value(table, "auto-executables", self%auto_executables, .true., stat=stat)
@@ -128,11 +131,14 @@ subroutine new_build_config(self, table, error)
128131
end subroutine new_build_config
129132

130133
!> Check local schema for allowed entries
131-
subroutine check(table, error)
134+
subroutine check(table, package_name, error)
132135

133136
!> Instance of the TOML data structure
134137
type(toml_table), intent(inout) :: table
135138

139+
!> Package name
140+
character(len=*), intent(in) :: package_name
141+
136142
!> Error handling
137143
type(error_t), allocatable, intent(out) :: error
138144

@@ -154,7 +160,9 @@ subroutine check(table, error)
154160
continue
155161

156162
case default
157-
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]")
163+
164+
call syntax_error(error, 'Manifest file syntax error: key "'//list(ikey)%key//'" found in the [build] '//&
165+
'section of package/dependency "'//package_name//'" fpm.toml is not allowed')
158166
exit
159167

160168
end select

src/fpm/manifest/package.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -172,7 +172,7 @@ subroutine new_package(self, table, root, error)
172172
call fatal_error(error, "Type mismatch for build entry, must be a table")
173173
return
174174
end if
175-
call new_build_config(self%build, child, error)
175+
call new_build_config(self%build, child, self%name, error)
176176
if (allocated(error)) return
177177

178178
call get_value(table, "install", child, requested=.true., stat=stat)
@@ -232,7 +232,7 @@ subroutine new_package(self, table, root, error)
232232
call new_library(self%library, child, error)
233233
if (allocated(error)) return
234234
end if
235-
235+
236236
call get_value(table, "profiles", child, requested=.false.)
237237
if (associated(child)) then
238238
call new_profiles(self%profiles, child, error)
@@ -442,7 +442,7 @@ subroutine info(self, unit, verbosity)
442442
call self%dev_dependency(ii)%info(unit, pr - 1)
443443
end do
444444
end if
445-
445+
446446
if (allocated(self%profiles)) then
447447
if (size(self%profiles) > 1 .or. pr > 2) then
448448
write(unit, fmti) "- profiles", size(self%profiles)

test/fpm_test/test_manifest.f90

Lines changed: 51 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module test_manifest
55
use fpm_manifest
66
use fpm_manifest_profile, only: profile_config_t, find_profile
77
use fpm_strings, only: operator(.in.)
8+
use fpm_error, only: fatal_error, error_t
89
implicit none
910
private
1011
public :: collect_manifest
@@ -42,6 +43,7 @@ subroutine collect_manifest(tests)
4243
& new_unittest("build-config-valid", test_build_valid), &
4344
& new_unittest("build-config-empty", test_build_empty), &
4445
& new_unittest("build-config-invalid-values", test_build_invalid_values, should_fail=.true.), &
46+
& new_unittest("build-key-invalid", test_build_invalid_key), &
4547
& new_unittest("library-empty", test_library_empty), &
4648
& new_unittest("library-wrongkey", test_library_wrongkey, should_fail=.true.), &
4749
& new_unittest("package-simple", test_package_simple), &
@@ -693,6 +695,52 @@ subroutine test_build_valid(error)
693695
end subroutine test_build_valid
694696

695697

698+
!> Try to read values from the [build] table
699+
subroutine test_build_invalid_key(error)
700+
701+
!> Error handling
702+
type(error_t), allocatable, intent(out) :: error
703+
704+
type(package_config_t) :: package
705+
character(:), allocatable :: temp_file
706+
integer :: unit
707+
type(error_t), allocatable :: build_error
708+
709+
allocate(temp_file, source=get_temp_filename())
710+
711+
open(file=temp_file, newunit=unit)
712+
write(unit, '(a)') &
713+
& 'name = "example"', &
714+
& '[build]', &
715+
& 'auto-executables = false', &
716+
& 'auto-tests = false ', &
717+
& 'module-naming = true ', &
718+
& 'this-will-fail = true '
719+
close(unit)
720+
721+
call get_package_data(package, temp_file, build_error)
722+
723+
! Error message should contain both package name and key name
724+
if (allocated(build_error)) then
725+
726+
if (.not.index(build_error%message,'this-will-fail')>0) then
727+
call fatal_error(error, 'no invalid key name is printed to output')
728+
return
729+
end if
730+
731+
if (.not.index(build_error%message,'example')>0) then
732+
call fatal_error(error, 'no package name is printed to output')
733+
return
734+
end if
735+
736+
else
737+
call fatal_error(error, 'no error allocated on invalid [build] section key ')
738+
return
739+
end if
740+
741+
end subroutine test_build_invalid_key
742+
743+
696744
!> Try to read values from an empty [build] table
697745
subroutine test_build_empty(error)
698746

@@ -1156,7 +1204,7 @@ subroutine test_link_string(error)
11561204
table = toml_table()
11571205
call set_value(table, "link", "z", stat=stat)
11581206

1159-
call new_build_config(build, table, error)
1207+
call new_build_config(build, table, 'test_link_string', error)
11601208

11611209
end subroutine test_link_string
11621210

@@ -1179,7 +1227,7 @@ subroutine test_link_array(error)
11791227
call set_value(children, 1, "blas", stat=stat)
11801228
call set_value(children, 2, "lapack", stat=stat)
11811229

1182-
call new_build_config(build, table, error)
1230+
call new_build_config(build, table, 'test_link_array', error)
11831231

11841232
end subroutine test_link_array
11851233

@@ -1200,7 +1248,7 @@ subroutine test_invalid_link(error)
12001248
table = toml_table()
12011249
call add_table(table, "link", child, stat=stat)
12021250

1203-
call new_build_config(build, table, error)
1251+
call new_build_config(build, table, 'test_invalid_link', error)
12041252

12051253
end subroutine test_invalid_link
12061254

0 commit comments

Comments
 (0)