Skip to content

Commit 99da449

Browse files
committed
Add: [build] table to manifest with flags for auto-discovery
1 parent f10b174 commit 99da449

File tree

4 files changed

+188
-8
lines changed

4 files changed

+188
-8
lines changed

fpm/src/fpm.f90

Lines changed: 17 additions & 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, package_t
16+
default_library, default_build_config, package_t
1717
use fpm_error, only : error_t
1818
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
1919
& stdout=>output_unit, &
@@ -57,7 +57,7 @@ subroutine build_model(model, settings, package, error)
5757
model%link_flags = ''
5858

5959
! Add sources from executable directories
60-
if (is_dir('app')) then
60+
if (is_dir('app') .and. package%build_config%auto_executables) then
6161
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
6262
with_executables=.true., error=error)
6363

@@ -66,7 +66,7 @@ subroutine build_model(model, settings, package, error)
6666
end if
6767

6868
end if
69-
if (is_dir('test')) then
69+
if (is_dir('test') .and. package%build_config%auto_tests) then
7070
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
7171
with_executables=.true., error=error)
7272

@@ -76,17 +76,19 @@ subroutine build_model(model, settings, package, error)
7676

7777
end if
7878
if (allocated(package%executable)) then
79-
call add_executable_sources(model%sources, package%executable, &
80-
FPM_SCOPE_APP, auto_discover=.true., error=error)
79+
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
80+
auto_discover=package%build_config%auto_executables, &
81+
error=error)
8182

8283
if (allocated(error)) then
8384
return
8485
end if
8586

8687
end if
8788
if (allocated(package%test)) then
88-
call add_executable_sources(model%sources, package%test, &
89-
FPM_SCOPE_TEST, auto_discover=.true., error=error)
89+
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
90+
auto_discover=package%build_config%auto_tests, &
91+
error=error)
9092

9193
if (allocated(error)) then
9294
return
@@ -119,6 +121,14 @@ subroutine cmd_build(settings)
119121
error stop 1
120122
end if
121123

124+
call package%info(stdout,10)
125+
126+
! Populate default build configuration if not included
127+
if (.not.allocated(package%build_config)) then
128+
allocate(package%build_config)
129+
call default_build_config(package%build_config)
130+
end if
131+
122132
! Populate library in case we find the default src directory
123133
if (.not.allocated(package%library) .and. exists("src")) then
124134
allocate(package%library)

fpm/src/fpm/manifest.f90

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@
77
! Additionally, the required data types for users of this module are reexported
88
! to hide the actual implementation details.
99
module fpm_manifest
10+
use fpm_manifest_build_config, only: build_config_t
1011
use fpm_manifest_executable, only : executable_t
1112
use fpm_manifest_library, only : library_t
1213
use fpm_manifest_package, only : package_t, new_package
@@ -16,12 +17,25 @@ module fpm_manifest
1617
private
1718

1819
public :: get_package_data, default_executable, default_library
20+
public :: default_build_config
1921
public :: package_t
2022

2123

2224
contains
2325

2426

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+
2539
!> Populate library in case we find the default src directory
2640
subroutine default_library(self)
2741

Lines changed: 140 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,140 @@
1+
!> Implementation of the build configuration data.
2+
!
3+
! A build table can currently have the following fields
4+
!
5+
! ```toml
6+
! [build]
7+
! auto-executables = <bool>
8+
! auto-tests = <bool>
9+
! ```
10+
module fpm_manifest_build_config
11+
use fpm_error, only : error_t, syntax_error, fatal_error
12+
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
13+
implicit none
14+
private
15+
16+
public :: build_config_t, new_build_config
17+
18+
19+
!> Configuration data for build
20+
type :: build_config_t
21+
22+
!> Automatic discovery of executables
23+
logical :: auto_executables
24+
25+
!> Automatic discovery of tests
26+
logical :: auto_tests
27+
28+
contains
29+
30+
!> Print information on this instance
31+
procedure :: info
32+
33+
end type build_config_t
34+
35+
36+
contains
37+
38+
39+
!> Construct a new build configuration from a TOML data structure
40+
subroutine new_build_config(self, table, error)
41+
42+
!> Instance of the build configuration
43+
type(build_config_t), intent(out) :: self
44+
45+
!> Instance of the TOML data structure
46+
type(toml_table), intent(inout) :: table
47+
48+
!> Error handling
49+
type(error_t), allocatable, intent(out) :: error
50+
51+
!> Status
52+
integer :: stat
53+
54+
call check(table, error)
55+
if (allocated(error)) return
56+
57+
call get_value(table, "auto-executables", self%auto_executables, .true., stat=stat)
58+
59+
if (stat /= toml_stat%success) then
60+
call fatal_error(error,"Error while reading value for 'auto-executables' in fpm.toml, expecting logical")
61+
return
62+
end if
63+
64+
call get_value(table, "auto-tests", self%auto_tests, .true., stat=stat)
65+
66+
if (stat /= toml_stat%success) then
67+
call fatal_error(error,"Error while reading value for 'auto-tests' in fpm.toml, expecting logical")
68+
return
69+
end if
70+
71+
end subroutine new_build_config
72+
73+
74+
!> Check local schema for allowed entries
75+
subroutine check(table, error)
76+
77+
!> Instance of the TOML data structure
78+
type(toml_table), intent(inout) :: table
79+
80+
!> Error handling
81+
type(error_t), allocatable, intent(out) :: error
82+
83+
type(toml_key), allocatable :: list(:)
84+
integer :: ikey
85+
86+
call table%get_keys(list)
87+
88+
! table can be empty
89+
if (size(list) < 1) return
90+
91+
do ikey = 1, size(list)
92+
select case(list(ikey)%key)
93+
94+
case("auto-executables", "auto-tests")
95+
continue
96+
97+
case default
98+
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in [build]")
99+
exit
100+
101+
end select
102+
end do
103+
104+
end subroutine check
105+
106+
107+
!> Write information on build configuration instance
108+
subroutine info(self, unit, verbosity)
109+
110+
!> Instance of the build configuration
111+
class(build_config_t), intent(in) :: self
112+
113+
!> Unit for IO
114+
integer, intent(in) :: unit
115+
116+
!> Verbosity of the printout
117+
integer, intent(in), optional :: verbosity
118+
119+
integer :: pr
120+
character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)'
121+
122+
if (present(verbosity)) then
123+
pr = verbosity
124+
else
125+
pr = 1
126+
end if
127+
128+
if (pr < 1) return
129+
130+
write(unit, fmt) "Build configuration"
131+
! if (allocated(self%auto_executables)) then
132+
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
133+
! end if
134+
! if (allocated(self%auto_tests)) then
135+
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
136+
! end if
137+
138+
end subroutine info
139+
140+
end module fpm_manifest_build_config

fpm/src/fpm/manifest/package.f90

Lines changed: 17 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@
2828
! [[test]]
2929
! ```
3030
module fpm_manifest_package
31+
use fpm_manifest_build_config, only: build_config_t, new_build_config
3132
use fpm_manifest_dependency, only : dependency_t, new_dependencies
3233
use fpm_manifest_executable, only : executable_t, new_executable
3334
use fpm_manifest_library, only : library_t, new_library
@@ -47,6 +48,9 @@ module fpm_manifest_package
4748
!> Name of the package
4849
character(len=:), allocatable :: name
4950

51+
!> Build configuration data
52+
type(build_config_t), allocatable :: build_config
53+
5054
!> Library meta data
5155
type(library_t), allocatable :: library
5256

@@ -98,6 +102,13 @@ subroutine new_package(self, table, error)
98102
return
99103
end if
100104

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
110+
end if
111+
101112
call get_value(table, "dependencies", child, requested=.false.)
102113
if (associated(child)) then
103114
call new_dependencies(self%dependency, child, error)
@@ -184,7 +195,7 @@ subroutine check(table, error)
184195
name_present = .true.
185196

186197
case("version", "license", "author", "maintainer", "copyright", &
187-
& "description", "keywords", "categories", "homepage", &
198+
& "description", "keywords", "categories", "homepage", "build", &
188199
& "dependencies", "dev-dependencies", "test", "executable", &
189200
& "library")
190201
continue
@@ -229,6 +240,11 @@ subroutine info(self, unit, verbosity)
229240
write(unit, fmt) "- name", self%name
230241
end if
231242

243+
if (allocated(self%build_config)) then
244+
write(unit, fmt) "- build configuration", ""
245+
call self%build_config%info(unit, pr - 1)
246+
end if
247+
232248
if (allocated(self%library)) then
233249
write(unit, fmt) "- target", "archive"
234250
call self%library%info(unit, pr - 1)

0 commit comments

Comments
 (0)