Skip to content

Commit fc8cab5

Browse files
LKedwardawvwgk
andauthored
Let toml-f make [build] table while querying the data structure
No need for separate default initializer for build table. Co-authored-by: Sebastian Ehlert <[email protected]>
1 parent ad02416 commit fc8cab5

File tree

4 files changed

+8
-52
lines changed

4 files changed

+8
-52
lines changed

fpm/src/fpm.f90

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ module fpm
1313
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
1414
resolve_module_dependencies
1515
use fpm_manifest, only : get_package_data, default_executable, &
16-
default_library, default_build_config, package_t
16+
default_library, package_t
1717
use fpm_error, only : error_t
1818
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
1919
& stdout=>output_unit, &
@@ -121,12 +121,6 @@ subroutine cmd_build(settings)
121121
error stop 1
122122
end if
123123

124-
! Populate default build configuration if not included
125-
if (.not.allocated(package%build_config)) then
126-
allocate(package%build_config)
127-
call default_build_config(package%build_config)
128-
end if
129-
130124
! Populate library in case we find the default src directory
131125
if (.not.allocated(package%library) .and. exists("src")) then
132126
allocate(package%library)

fpm/src/fpm/manifest.f90

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -17,25 +17,12 @@ module fpm_manifest
1717
private
1818

1919
public :: get_package_data, default_executable, default_library
20-
public :: default_build_config
2120
public :: package_t
2221

2322

2423
contains
2524

2625

27-
!> Populate build configuration with defaults
28-
subroutine default_build_config(self)
29-
30-
!> Instance of the build configuration data
31-
type(build_config_t), intent(out) :: self
32-
33-
self%auto_executables = .true.
34-
self%auto_tests = .true.
35-
36-
end subroutine default_build_config
37-
38-
3926
!> Populate library in case we find the default src directory
4027
subroutine default_library(self)
4128

fpm/src/fpm/manifest/package.f90

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -102,12 +102,14 @@ subroutine new_package(self, table, error)
102102
return
103103
end if
104104

105-
call get_value(table, "build", child, requested=.false.)
106-
if (associated(child)) then
107-
allocate(self%build_config)
108-
call new_build_config(self%build_config, child, error)
109-
if (allocated(error)) return
105+
call get_value(table, "build", child, requested=.true., stat=stat)
106+
if (stat /= toml_stat%success) then
107+
call fatal_error(error, "Type mismatch for build entry, must be a table")
108+
return
110109
end if
110+
allocate(self%build_config)
111+
call new_build_config(self%build_config, child, error)
112+
if (allocated(error)) return
111113

112114
call get_value(table, "dependencies", child, requested=.false.)
113115
if (associated(child)) then
@@ -241,7 +243,6 @@ subroutine info(self, unit, verbosity)
241243
end if
242244

243245
if (allocated(self%build_config)) then
244-
write(unit, fmt) "- build configuration", ""
245246
call self%build_config%info(unit, pr - 1)
246247
end if
247248

fpm/test/fpm_test/test_manifest.f90

Lines changed: 0 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ subroutine collect_manifest(testsuite)
2222
testsuite = [ &
2323
& new_unittest("valid-manifest", test_valid_manifest), &
2424
& new_unittest("invalid-manifest", test_invalid_manifest, should_fail=.true.), &
25-
& new_unittest("default-build-configuration", test_default_build_config), &
2625
& new_unittest("default-library", test_default_library), &
2726
& new_unittest("default-executable", test_default_executable), &
2827
& new_unittest("dependency-empty", test_dependency_empty, should_fail=.true.), &
@@ -165,31 +164,6 @@ subroutine test_invalid_manifest(error)
165164
end subroutine test_invalid_manifest
166165

167166

168-
!> Create a default build configuration
169-
subroutine test_default_build_config(error)
170-
171-
!> Error handling
172-
type(error_t), allocatable, intent(out) :: error
173-
174-
type(package_t) :: package
175-
176-
allocate(package%build_config)
177-
call default_build_config(package%build_config)
178-
179-
if (.not. package%build_config%auto_executables) then
180-
call test_failed(error,'Incorrect value for auto_executables in default build configuration, expecting .true.')
181-
return
182-
end if
183-
184-
if (.not. package%build_config%auto_tests) then
185-
call test_failed(error,'Incorrect value for auto_tests in default build configuration, expecting .true.')
186-
return
187-
end if
188-
189-
190-
end subroutine test_default_build_config
191-
192-
193167
!> Create a default library
194168
subroutine test_default_library(error)
195169

0 commit comments

Comments
 (0)