Skip to content

Commit 75c1da5

Browse files
authored
Merge pull request #190 from LKedward/auto-discovery
Auto discovery of executables
2 parents 0c35749 + 0fe14b8 commit 75c1da5

30 files changed

+1053
-58
lines changed

ci/run_tests.bat

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,41 @@ if errorlevel 1 exit 1
4444
if errorlevel 1 exit 1
4545

4646

47+
cd ..\hello_complex_2
48+
if errorlevel 1 exit 1
49+
50+
..\..\..\fpm\build\gfortran_debug\app\fpm build
51+
if errorlevel 1 exit 1
52+
53+
.\build\gfortran_debug\app\say_hello_world
54+
if errorlevel 1 exit 1
55+
56+
.\build\gfortran_debug\app\say_goodbye
57+
if errorlevel 1 exit 1
58+
59+
.\build\gfortran_debug\test\greet_test
60+
if errorlevel 1 exit 1
61+
62+
.\build\gfortran_debug\test\farewell_test
63+
64+
65+
cd ..\auto_discovery_off
66+
if errorlevel 1 exit 1
67+
68+
..\..\..\fpm\build\gfortran_debug\app\fpm build
69+
if errorlevel 1 exit 1
70+
71+
.\build\gfortran_debug\app\auto_discovery_off
72+
if errorlevel 1 exit 1
73+
74+
.\build\gfortran_debug\test\my_test
75+
if errorlevel 1 exit 1
76+
77+
if exist .\build\gfortran_debug\app\unused exit /B 1
78+
79+
if exist .\build\gfortran_debug\test\unused_test exit /B 1
80+
81+
4782
cd ..\with_c
4883
if errorlevel 1 exit 1
4984

ci/run_tests.sh

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,20 @@ cd ../hello_complex
1919
./build/gfortran_debug/test/greet_test
2020
./build/gfortran_debug/test/farewell_test
2121

22+
cd ../hello_complex_2
23+
../../../fpm/build/gfortran_debug/app/fpm build
24+
./build/gfortran_debug/app/say_hello_world
25+
./build/gfortran_debug/app/say_goodbye
26+
./build/gfortran_debug/test/greet_test
27+
./build/gfortran_debug/test/farewell_test
28+
29+
cd ../auto_discovery_off
30+
../../../fpm/build/gfortran_debug/app/fpm build
31+
./build/gfortran_debug/app/auto_discovery_off
32+
./build/gfortran_debug/test/my_test
33+
test ! -x ./build/gfortran_debug/app/unused
34+
test ! -x ./build/gfortran_debug/test/unused_test
35+
2236
cd ../with_c
2337
../../../fpm/build/gfortran_debug/app/fpm build
2438
./build/gfortran_debug/app/with_c
@@ -28,4 +42,4 @@ cd ../submodules
2842

2943
cd ../program_with_module
3044
../../../fpm/build/gfortran_debug/app/fpm build
31-
./build/gfortran_debug/app/Program_with_module
45+
./build/gfortran_debug/app/Program_with_module

fpm/src/fpm.f90

Lines changed: 35 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,11 @@ module fpm
55
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
66
fpm_run_settings, fpm_install_settings, fpm_test_settings
77
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
8-
use fpm_filesystem, only: join_path, number_of_rows, list_files, exists, basename
9-
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t
8+
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
9+
use fpm_model, only: srcfile_ptr, srcfile_t, fpm_model_t, &
10+
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
11+
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
12+
1013
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
1114
resolve_module_dependencies
1215
use fpm_manifest, only : get_package_data, default_executable, &
@@ -54,20 +57,38 @@ subroutine build_model(model, settings, package, error)
5457
model%link_flags = ''
5558

5659
! Add sources from executable directories
57-
if (allocated(package%executable)) then
60+
if (is_dir('app') .and. package%build_config%auto_executables) then
61+
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
62+
with_executables=.true., error=error)
63+
64+
if (allocated(error)) then
65+
return
66+
end if
5867

59-
call add_executable_sources(model%sources, package%executable, &
60-
is_test=.false., error=error)
68+
end if
69+
if (is_dir('test') .and. package%build_config%auto_tests) then
70+
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
71+
with_executables=.true., error=error)
6172

6273
if (allocated(error)) then
6374
return
6475
end if
6576

6677
end if
67-
if (allocated(package%test)) then
78+
if (allocated(package%executable)) then
79+
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
80+
auto_discover=package%build_config%auto_executables, &
81+
error=error)
82+
83+
if (allocated(error)) then
84+
return
85+
end if
6886

69-
call add_executable_sources(model%sources, package%test, &
70-
is_test=.true., error=error)
87+
end if
88+
if (allocated(package%test)) then
89+
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
90+
auto_discover=package%build_config%auto_tests, &
91+
error=error)
7192

7293
if (allocated(error)) then
7394
return
@@ -76,17 +97,16 @@ subroutine build_model(model, settings, package, error)
7697
end if
7798

7899
if (allocated(package%library)) then
79-
80-
call add_sources_from_dir(model%sources,package%library%source_dir, &
81-
error=error)
100+
call add_sources_from_dir(model%sources, package%library%source_dir, &
101+
FPM_SCOPE_LIB, error=error)
82102

83103
if (allocated(error)) then
84104
return
85105
end if
86106

87107
end if
88108

89-
call resolve_module_dependencies(model%sources)
109+
call resolve_module_dependencies(model%sources,error)
90110

91111
end subroutine build_model
92112

@@ -107,8 +127,9 @@ subroutine cmd_build(settings)
107127
call default_library(package%library)
108128
end if
109129

110-
! Populate executable in case we find the default app directory
111-
if (.not.allocated(package%executable) .and. exists("app")) then
130+
! Populate executable in case we find the default app
131+
if (.not.allocated(package%executable) .and. &
132+
exists(join_path('app',"main.f90"))) then
112133
allocate(package%executable(1))
113134
call default_executable(package%executable(1), package%name)
114135
end if

fpm/src/fpm/manifest.f90

Lines changed: 1 addition & 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
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
@@ -48,6 +49,9 @@ module fpm_manifest_package
4849
!> Name of the package
4950
character(len=:), allocatable :: name
5051

52+
!> Build configuration data
53+
type(build_config_t) :: build_config
54+
5155
!> Package version
5256
type(version_t) :: version
5357

@@ -103,8 +107,18 @@ subroutine new_package(self, table, error)
103107
return
104108
end if
105109

110+
call get_value(table, "build", child, requested=.true., stat=stat)
111+
if (stat /= toml_stat%success) then
112+
call fatal_error(error, "Type mismatch for build entry, must be a table")
113+
return
114+
end if
115+
call new_build_config(self%build_config, child, error)
116+
117+
if (allocated(error)) return
118+
106119
call get_value(table, "version", version, "0")
107120
call new_version(self%version, version, error)
121+
108122
if (allocated(error)) return
109123

110124
call get_value(table, "dependencies", child, requested=.false.)
@@ -193,7 +207,7 @@ subroutine check(table, error)
193207
name_present = .true.
194208

195209
case("version", "license", "author", "maintainer", "copyright", &
196-
& "description", "keywords", "categories", "homepage", &
210+
& "description", "keywords", "categories", "homepage", "build", &
197211
& "dependencies", "dev-dependencies", "test", "executable", &
198212
& "library")
199213
continue
@@ -238,6 +252,8 @@ subroutine info(self, unit, verbosity)
238252
write(unit, fmt) "- name", self%name
239253
end if
240254

255+
call self%build_config%info(unit, pr - 1)
256+
241257
if (allocated(self%library)) then
242258
write(unit, fmt) "- target", "archive"
243259
call self%library%info(unit, pr - 1)

fpm/src/fpm_backend.f90

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,9 @@ module fpm_backend
66
use fpm_filesystem, only: basename, join_path, exists, mkdir
77
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
88
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
9-
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM
9+
FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, &
10+
FPM_SCOPE_TEST
11+
1012
use fpm_strings, only: split
1113

1214
implicit none
@@ -59,7 +61,7 @@ subroutine build_package(model)
5961

6062
base = basename(model%sources(i)%file_name,suffix=.false.)
6163

62-
if (model%sources(i)%is_test) then
64+
if (model%sources(i)%unit_scope == FPM_SCOPE_TEST) then
6365
subdir = 'test'
6466
else
6567
subdir = 'app'

0 commit comments

Comments
 (0)