Skip to content

Commit 9369cc2

Browse files
authored
Merge branch 'master' into NEW
2 parents 07c5330 + 75c1da5 commit 9369cc2

30 files changed

+1092
-102
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: 74 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,17 @@
11
module fpm
22

3-
use fpm_strings, only : string_t, str_ends_with
4-
use fpm_backend, only : build_package
5-
use fpm_command_line, only : fpm_build_settings, fpm_new_settings, &
6-
fpm_run_settings, fpm_install_settings, fpm_test_settings
7-
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, mkdir
9-
use fpm_model, only : srcfile_ptr, srcfile_t, fpm_model_t
10-
use fpm_sources, only : add_executable_sources, add_sources_from_dir, &
11-
resolve_module_dependencies
3+
use fpm_strings, only: string_t, str_ends_with
4+
use fpm_backend, only: build_package
5+
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
6+
fpm_run_settings, fpm_install_settings, fpm_test_settings
7+
use fpm_environment, only: run, get_os_type, OS_LINUX, OS_MACOS, OS_WINDOWS
8+
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename, mkdir
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+
13+
use fpm_sources, only: add_executable_sources, add_sources_from_dir, &
14+
resolve_module_dependencies
1215
use fpm_manifest, only : get_package_data, default_executable, &
1316
default_library, package_t, default_test
1417
use fpm_error, only : error_t
@@ -56,20 +59,38 @@ subroutine build_model(model, settings, package, error)
5659
model%link_flags = ''
5760

5861
! Add sources from executable directories
59-
if (allocated(package%executable)) then
62+
if (is_dir('app') .and. package%build_config%auto_executables) then
63+
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
64+
with_executables=.true., error=error)
6065

61-
call add_executable_sources(model%sources, package%executable, &
62-
is_test=.false., error=error)
66+
if (allocated(error)) then
67+
return
68+
end if
69+
70+
end if
71+
if (is_dir('test') .and. package%build_config%auto_tests) then
72+
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
73+
with_executables=.true., error=error)
6374

6475
if (allocated(error)) then
6576
return
6677
endif
6778

68-
endif
69-
if (allocated(package%test)) then
79+
end if
80+
if (allocated(package%executable)) then
81+
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
82+
auto_discover=package%build_config%auto_executables, &
83+
error=error)
84+
85+
if (allocated(error)) then
86+
return
87+
end if
7088

71-
call add_executable_sources(model%sources, package%test, &
72-
is_test=.true., error=error)
89+
end if
90+
if (allocated(package%test)) then
91+
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
92+
auto_discover=package%build_config%auto_tests, &
93+
error=error)
7394

7495
if (allocated(error)) then
7596
return
@@ -79,13 +100,14 @@ subroutine build_model(model, settings, package, error)
79100

80101
if (allocated(package%library)) then
81102

82-
call add_sources_from_dir(model%sources,package%library%source_dir, &
83-
error=error)
103+
call add_sources_from_dir(model%sources, package%library%source_dir, &
104+
FPM_SCOPE_LIB, error=error)
84105

85106
if (allocated(error)) then
86107
return
87108
endif
88109

110+
89111
endif
90112
if(settings%list)then
91113
do i=1,size(model%sources)
@@ -94,7 +116,7 @@ subroutine build_model(model, settings, package, error)
94116
enddo
95117
stop
96118
else
97-
call resolve_module_dependencies(model%sources)
119+
call resolve_module_dependencies(model%sources,error)
98120
endif
99121

100122
end subroutine build_model
@@ -106,45 +128,39 @@ subroutine cmd_build(settings)
106128
type(fpm_model_t) :: model
107129
type(error_t), allocatable :: error
108130

109-
call get_package_data(package, "fpm.toml", error)
110-
if (allocated(error)) then
111-
print '(a)', error%message
112-
error stop 5
113-
endif
114-
115-
! Populate library in case we find the default src directory
116-
if (.not.allocated(package%library) .and. exists("src")) then
117-
allocate(package%library)
118-
call default_library(package%library)
119-
endif
120-
121-
! Populate executable in case we find the default app directory
122-
if (.not.allocated(package%executable) .and. exists("app")) then
123-
allocate(package%executable(1))
124-
call default_executable(package%executable(1), package%name)
125-
endif
126-
127-
! Populate test in case we find the default test directory
128-
if (.not.allocated(package%test) .and. exists("test")) then
129-
allocate(package%test(1))
130-
call default_test(package%test(1), package%name)
131-
endif
132-
133-
if (.not.(allocated(package%library) .or. allocated(package%executable) .or. allocated(package%test) )) then
134-
print '(a)', "Neither library nor executable found, there is nothing to do"
135-
error stop 6
136-
endif
137-
138-
call build_model(model, settings, package, error)
139-
if (allocated(error)) then
140-
print '(a)', error%message
141-
error stop 7
142-
endif
143-
144-
call build_package(model)
145-
146-
end subroutine cmd_build
147-
131+
call get_package_data(package, "fpm.toml", error)
132+
if (allocated(error)) then
133+
print '(a)', error%message
134+
error stop 1
135+
end if
136+
137+
! Populate library in case we find the default src directory
138+
if (.not.allocated(package%library) .and. exists("src")) then
139+
allocate(package%library)
140+
call default_library(package%library)
141+
end if
142+
143+
! Populate executable in case we find the default app
144+
if (.not.allocated(package%executable) .and. &
145+
exists(join_path('app',"main.f90"))) then
146+
allocate(package%executable(1))
147+
call default_executable(package%executable(1), package%name)
148+
end if
149+
150+
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
151+
print '(a)', "Neither library nor executable found, there is nothing to do"
152+
error stop 1
153+
end if
154+
155+
call build_model(model, settings, package, error)
156+
if (allocated(error)) then
157+
print '(a)', error%message
158+
error stop 1
159+
end if
160+
161+
call build_package(model)
162+
163+
end subroutine
148164

149165
subroutine cmd_install(settings)
150166
type(fpm_install_settings), intent(in) :: settings

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

0 commit comments

Comments
 (0)