Skip to content

Commit 6bb5f6c

Browse files
authored
Build no tests by default (#572)
Building tests can be enforced using --tests for build. It is done automatically before running tests.
1 parent edb3fcd commit 6bb5f6c

File tree

5 files changed

+23
-5
lines changed

5 files changed

+23
-5
lines changed

src/fpm.f90

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,8 @@ subroutine build_model(model, settings, package, error)
8585
model%fortran_compile_flags = flags // " " // &
8686
& model%compiler%get_module_flag(join_path(model%output_directory, model%package_name))
8787

88+
model%include_tests = settings%build_tests
89+
8890
allocate(model%packages(model%deps%ndep))
8991

9092
! Add sources from executable directories
@@ -268,7 +270,7 @@ subroutine cmd_build(settings)
268270
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
269271
end if
270272

271-
call targets_from_sources(targets,model,error)
273+
call targets_from_sources(targets, model, error)
272274
if (allocated(error)) then
273275
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
274276
end if
@@ -314,7 +316,7 @@ subroutine cmd_run(settings,test)
314316
call fpm_stop(1, '*cmd_run*:model error:'//error%message)
315317
end if
316318

317-
call targets_from_sources(targets,model,error)
319+
call targets_from_sources(targets, model, error)
318320
if (allocated(error)) then
319321
call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
320322
end if

src/fpm/cmd/install.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -36,7 +36,7 @@ subroutine cmd_install(settings)
3636
call build_model(model, settings%fpm_build_settings, package, error)
3737
call handle_error(error)
3838

39-
call targets_from_sources(targets,model,error)
39+
call targets_from_sources(targets, model, error)
4040
call handle_error(error)
4141

4242
installable = (allocated(package%library) .and. package%install%library) &

src/fpm_command_line.f90

Lines changed: 11 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -67,6 +67,7 @@ module fpm_command_line
6767
type, extends(fpm_cmd_settings) :: fpm_build_settings
6868
logical :: list=.false.
6969
logical :: show_model=.false.
70+
logical :: build_tests=.false.
7071
character(len=:),allocatable :: compiler
7172
character(len=:),allocatable :: profile
7273
character(len=:),allocatable :: flag
@@ -202,6 +203,7 @@ subroutine get_command_line_settings(cmd_settings)
202203
& flag=val_flag, &
203204
& example=lget('example'), &
204205
& list=lget('list'),&
206+
& build_tests=.false.,&
205207
& name=names,&
206208
& runner=val_runner,&
207209
& verbose=lget('verbose') )
@@ -213,7 +215,8 @@ subroutine get_command_line_settings(cmd_settings)
213215
& --show-model F &
214216
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
215217
& --flag:: " "&
216-
& --verbose F&
218+
& --tests F &
219+
& --verbose F &
217220
& --',help_build,version_text)
218221

219222
call check_build_vals()
@@ -225,6 +228,7 @@ subroutine get_command_line_settings(cmd_settings)
225228
& flag=val_flag, &
226229
& list=lget('list'),&
227230
& show_model=lget('show-model'),&
231+
& build_tests=lget('tests'),&
228232
& verbose=lget('verbose') )
229233

230234
case('new')
@@ -417,6 +421,7 @@ subroutine get_command_line_settings(cmd_settings)
417421
& flag=val_flag, &
418422
& example=.false., &
419423
& list=lget('list'), &
424+
& build_tests=.true., &
420425
& name=names, &
421426
& runner=val_runner, &
422427
& verbose=lget('verbose') )
@@ -521,6 +526,7 @@ subroutine set_help()
521526
help_list_dash = [character(len=80) :: &
522527
' ', &
523528
' build [--compiler COMPILER_NAME] [--profile PROF] [--flag FFLAGS] [--list] ', &
529+
' [--tests] ', &
524530
' help [NAME(s)] ', &
525531
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
526532
' [--full|--bare][--backfill] ', &
@@ -638,6 +644,7 @@ subroutine set_help()
638644
' Their syntax is ', &
639645
' ', &
640646
' build [--profile PROF] [--flag FFLAGS] [--list] [--compiler COMPILER_NAME] ', &
647+
' [--tests] ', &
641648
' new NAME [[--lib|--src] [--app] [--test] [--example]]| ', &
642649
' [--full|--bare][--backfill] ', &
643650
' update [NAME(s)] [--fetch-only] [--clean] ', &
@@ -828,7 +835,8 @@ subroutine set_help()
828835
' build(1) - the fpm(1) subcommand to build a project ', &
829836
' ', &
830837
'SYNOPSIS ', &
831-
' fpm build [--profile PROF] [--flag FFLAGS] [--compiler COMPILER_NAME] [-list]', &
838+
' fpm build [--profile PROF] [--flag FFLAGS] [--compiler COMPILER_NAME] ', &
839+
' [--list] [--tests] ', &
832840
' ', &
833841
' fpm build --help|--version ', &
834842
' ', &
@@ -864,6 +872,7 @@ subroutine set_help()
864872
' "gfortran" unless set by the environment ', &
865873
' variable FPM_COMPILER. ', &
866874
' --list list candidates instead of building or running them ', &
875+
' --tests build all tests (otherwise only if needed) ', &
867876
' --show-model show the model and exit (do not build) ', &
868877
' --help print this help and exit ', &
869878
' --version print program version information and exit ', &

src/fpm_model.f90

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -139,6 +139,9 @@ module fpm_model
139139
!> Project dependencies
140140
type(dependency_tree_t) :: deps
141141

142+
!> Whether tests should be added to the build list
143+
logical :: include_tests = .true.
144+
142145
end type fpm_model_t
143146

144147
contains

src/fpm_targets.f90

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -191,6 +191,10 @@ subroutine build_target_list(targets,model)
191191

192192
do i=1,size(sources)
193193

194+
if (.not. model%include_tests) then
195+
if (sources(i)%unit_scope == FPM_SCOPE_TEST) cycle
196+
end if
197+
194198
select case (sources(i)%unit_type)
195199
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
196200

0 commit comments

Comments
 (0)