Skip to content

Commit 1f08686

Browse files
authored
Feat: option to install test programs (#1079)
2 parents d92053e + 60a21b4 commit 1f08686

File tree

5 files changed

+130
-12
lines changed

5 files changed

+130
-12
lines changed

src/fpm/cmd/install.f90

Lines changed: 30 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ module fpm_cmd_install
77
use fpm_filesystem, only : join_path, list_files
88
use fpm_installer, only : installer_t, new_installer
99
use fpm_manifest, only : package_config_t, get_package_data
10-
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
10+
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP, FPM_SCOPE_TEST
1111
use fpm_targets, only: targets_from_sources, build_target_t, &
1212
build_target_ptr, FPM_TARGET_EXECUTABLE, &
1313
filter_library_targets, filter_executable_targets, filter_modules
@@ -34,7 +34,7 @@ subroutine cmd_install(settings)
3434

3535
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
3636
call handle_error(error)
37-
37+
3838
call build_model(model, settings, package, error)
3939
call handle_error(error)
4040

@@ -57,7 +57,7 @@ subroutine cmd_install(settings)
5757
end if
5858

5959
call new_installer(installer, prefix=settings%prefix, &
60-
bindir=settings%bindir, libdir=settings%libdir, &
60+
bindir=settings%bindir, libdir=settings%libdir, testdir=settings%testdir, &
6161
includedir=settings%includedir, &
6262
verbosity=merge(2, 1, settings%verbose))
6363

@@ -72,12 +72,19 @@ subroutine cmd_install(settings)
7272
call handle_error(error)
7373
end if
7474
end if
75-
75+
7676
if (allocated(package%executable) .or. ntargets>0) then
7777
call install_executables(installer, targets, error)
7878
call handle_error(error)
7979
end if
8080

81+
if (allocated(package%test) .and. (package%install%test .or. model%include_tests)) then
82+
83+
call install_tests(installer, targets, error)
84+
call handle_error(error)
85+
86+
end if
87+
8188
end subroutine cmd_install
8289

8390
subroutine install_info(unit, verbose, targets, ntargets)
@@ -97,6 +104,9 @@ subroutine install_info(unit, verbose, targets, ntargets)
97104
call filter_executable_targets(targets, FPM_SCOPE_APP, temp)
98105
install_target = [install_target, temp]
99106

107+
call filter_executable_targets(targets, FPM_SCOPE_TEST, temp)
108+
install_target = [install_target, temp]
109+
100110
ntargets = size(install_target)
101111

102112
if (verbose) then
@@ -144,6 +154,22 @@ subroutine install_executables(installer, targets, error)
144154

145155
end subroutine install_executables
146156

157+
subroutine install_tests(installer, targets, error)
158+
type(installer_t), intent(inout) :: installer
159+
type(build_target_ptr), intent(in) :: targets(:)
160+
type(error_t), allocatable, intent(out) :: error
161+
integer :: ii
162+
163+
do ii = 1, size(targets)
164+
if (targets(ii)%ptr%is_executable_target(FPM_SCOPE_TEST)) then
165+
call installer%install_test(targets(ii)%ptr%output_file, error)
166+
if (allocated(error)) exit
167+
end if
168+
end do
169+
if (allocated(error)) return
170+
171+
end subroutine install_tests
172+
147173
subroutine handle_error(error)
148174
type(error_t), intent(in), optional :: error
149175
if (present(error)) then

src/fpm/installer.f90

Lines changed: 38 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,8 @@ module fpm_installer
2121
character(len=:), allocatable :: bindir
2222
!> Library directory relative to the installation prefix
2323
character(len=:), allocatable :: libdir
24+
!> Test program directory relative to the installation prefix
25+
character(len=:), allocatable :: testdir
2426
!> Include directory relative to the installation prefix
2527
character(len=:), allocatable :: includedir
2628
!> Output unit for informative printout
@@ -40,6 +42,8 @@ module fpm_installer
4042
procedure :: install_library
4143
!> Install a header/module in its correct subdirectory
4244
procedure :: install_header
45+
!> Install a test program in its correct subdirectory
46+
procedure :: install_test
4347
!> Install a generic file into a subdirectory in the installation prefix
4448
procedure :: install
4549
!> Run an installation command, type-bound for unit testing purposes
@@ -53,6 +57,9 @@ module fpm_installer
5357

5458
!> Default name of the library subdirectory
5559
character(len=*), parameter :: default_libdir = "lib"
60+
61+
!> Default name of the test subdirectory
62+
character(len=*), parameter :: default_testdir = "test"
5663

5764
!> Default name of the include subdirectory
5865
character(len=*), parameter :: default_includedir = "include"
@@ -78,7 +85,7 @@ module fpm_installer
7885
contains
7986

8087
!> Create a new instance of an installer
81-
subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
88+
subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verbosity, &
8289
copy, move)
8390
!> Instance of the installer
8491
type(installer_t), intent(out) :: self
@@ -90,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
9097
character(len=*), intent(in), optional :: libdir
9198
!> Include directory relative to the installation prefix
9299
character(len=*), intent(in), optional :: includedir
100+
!> Test directory relative to the installation prefix
101+
character(len=*), intent(in), optional :: testdir
93102
!> Verbosity of the installer
94103
integer, intent(in), optional :: verbosity
95104
!> Copy command
@@ -125,6 +134,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, &
125134
else
126135
self%includedir = default_includedir
127136
end if
137+
138+
if (present(testdir)) then
139+
self%testdir = testdir
140+
else
141+
self%testdir = default_testdir
142+
end if
128143

129144
if (present(prefix)) then
130145
self%prefix = prefix
@@ -186,6 +201,28 @@ subroutine install_library(self, library, error)
186201
call self%install(library, self%libdir, error)
187202
end subroutine install_library
188203

204+
!> Install a test program in its correct subdirectory
205+
subroutine install_test(self, test, error)
206+
!> Instance of the installer
207+
class(installer_t), intent(inout) :: self
208+
!> Path to the test executable
209+
character(len=*), intent(in) :: test
210+
!> Error handling
211+
type(error_t), allocatable, intent(out) :: error
212+
integer :: ll
213+
214+
if (.not.os_is_unix(self%os)) then
215+
ll = len(test)
216+
if (test(max(1, ll-3):ll) /= ".exe") then
217+
call self%install(test//".exe", self%testdir, error)
218+
return
219+
end if
220+
end if
221+
222+
call self%install(test, self%testdir, error)
223+
224+
end subroutine install_test
225+
189226
!> Install a header/module in its correct subdirectory
190227
subroutine install_header(self, header, error)
191228
!> Instance of the installer

src/fpm/manifest/install.f90

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,9 @@ module fpm_manifest_install
1818

1919
!> Install library with this project
2020
logical :: library = .false.
21+
22+
!> Install tests with this project
23+
logical :: test = .false.
2124

2225
contains
2326

@@ -51,6 +54,7 @@ subroutine new_install_config(self, table, error)
5154
if (allocated(error)) return
5255

5356
call get_value(table, "library", self%library, .false.)
57+
call get_value(table, "test", self%test, .false.)
5458

5559
end subroutine new_install_config
5660

@@ -75,8 +79,8 @@ subroutine check(table, error)
7579
case default
7680
call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in install table")
7781
exit
78-
case("library")
79-
continue
82+
case("library","test")
83+
continue
8084
end select
8185
end do
8286
if (allocated(error)) return
@@ -107,8 +111,8 @@ subroutine info(self, unit, verbosity)
107111
if (pr < 1) return
108112

109113
write(unit, fmt) "Install configuration"
110-
write(unit, fmt) " - library install", &
111-
& trim(merge("enabled ", "disabled", self%library))
114+
write(unit, fmt) " - library install", trim(merge("enabled ", "disabled", self%library))
115+
write(unit, fmt) " - test install", trim(merge("enabled ", "disabled", self%test))
112116

113117
end subroutine info
114118

@@ -121,6 +125,7 @@ logical function install_conf_same(this,that)
121125
select type (other=>that)
122126
type is (install_config_t)
123127
if (this%library.neqv.other%library) return
128+
if (this%test.neqv.other%test) return
124129
class default
125130
! Not the same type
126131
return
@@ -144,6 +149,10 @@ subroutine dump_to_toml(self, table, error)
144149
type(error_t), allocatable, intent(out) :: error
145150

146151
call set_value(table, "library", self%library, error, class_name)
152+
if (allocated(error)) return
153+
154+
call set_value(table, "test", self%test, error, class_name)
155+
if (allocated(error)) return
147156

148157
end subroutine dump_to_toml
149158

@@ -163,6 +172,8 @@ subroutine load_from_toml(self, table, error)
163172

164173
call get_value(table, "library", self%library, error, class_name)
165174
if (allocated(error)) return
175+
call get_value(table, "test", self%test, error, class_name)
176+
if (allocated(error)) return
166177

167178
end subroutine load_from_toml
168179

src/fpm_command_line.f90

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,7 @@ module fpm_command_line
108108
character(len=:), allocatable :: prefix
109109
character(len=:), allocatable :: bindir
110110
character(len=:), allocatable :: libdir
111+
character(len=:), allocatable :: testdir
111112
character(len=:), allocatable :: includedir
112113
logical :: no_rebuild
113114
end type
@@ -533,8 +534,8 @@ subroutine get_command_line_settings(cmd_settings)
533534
case('install')
534535
call set_args(common_args // compiler_args // '&
535536
& --no-rebuild F --prefix " " &
536-
& --list F &
537-
& --libdir "lib" --bindir "bin" --includedir "include"', &
537+
& --list F --test F &
538+
& --libdir "lib" --bindir "bin" --testdir "test" --includedir "include"', &
538539
help_install, version_text)
539540

540541
call check_build_vals()
@@ -544,6 +545,7 @@ subroutine get_command_line_settings(cmd_settings)
544545
archiver = sget('archiver')
545546
allocate(install_settings, source=fpm_install_settings(&
546547
list=lget('list'), &
548+
build_tests=lget('test'), &
547549
profile=val_profile,&
548550
prune=.not.lget('no-prune'), &
549551
compiler=val_compiler, &
@@ -558,6 +560,7 @@ subroutine get_command_line_settings(cmd_settings)
558560
verbose=lget('verbose')))
559561
call get_char_arg(install_settings%prefix, 'prefix')
560562
call get_char_arg(install_settings%libdir, 'libdir')
563+
call get_char_arg(install_settings%testdir, 'testdir')
561564
call get_char_arg(install_settings%bindir, 'bindir')
562565
call get_char_arg(install_settings%includedir, 'includedir')
563566
call move_alloc(install_settings, cmd_settings)
@@ -1418,6 +1421,7 @@ subroutine set_help()
14181421
help_text_build_common,&
14191422
help_text_flag, &
14201423
' --no-rebuild do not rebuild project before installation', &
1424+
' --test also install test programs', &
14211425
' --prefix DIR path to installation directory (requires write access),', &
14221426
' the default prefix on Unix systems is $HOME/.local', &
14231427
' and %APPDATA%\local on Windows', &
@@ -1426,6 +1430,7 @@ subroutine set_help()
14261430
' (default: lib)', &
14271431
' --includedir DIR subdirectory to place headers and module files in', &
14281432
' (default: include)', &
1433+
' --testdir DIR subdirectory to place test programs in (default: test)', &
14291434
' --verbose print more information', &
14301435
'', &
14311436
help_text_environment, &
@@ -1442,6 +1447,9 @@ subroutine set_help()
14421447
' 3. Install executables to a custom prefix into the exe directory:', &
14431448
'', &
14441449
' fpm install --prefix $PWD --bindir exe', &
1450+
' 4. Install executables and test programs into the same "exe" directory:', &
1451+
'', &
1452+
' fpm install --prefix $PWD --test --bindir exe --testdir exe', &
14451453
'' ]
14461454
help_clean=[character(len=80) :: &
14471455
'NAME', &

test/fpm_test/test_installer.f90

Lines changed: 37 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,9 @@ subroutine collect_installer(testsuite)
3535
& new_unittest("install-sitepackages", test_install_sitepackages), &
3636
& new_unittest("install-mod", test_install_mod), &
3737
& new_unittest("install-exe-unix", test_install_exe_unix), &
38-
& new_unittest("install-exe-win", test_install_exe_win)]
38+
& new_unittest("install-exe-win", test_install_exe_win), &
39+
& new_unittest("install-test-unix", test_install_tests_unix), &
40+
& new_unittest("install-test-win", test_install_tests_win)]
3941

4042
end subroutine collect_installer
4143

@@ -73,6 +75,40 @@ subroutine test_install_exe_win(error)
7375

7476
end subroutine test_install_exe_win
7577

78+
subroutine test_install_tests_unix(error)
79+
!> Error handling
80+
type(error_t), allocatable, intent(out) :: error
81+
82+
type(mock_installer_t) :: mock
83+
type(installer_t) :: installer
84+
85+
call new_installer(installer, prefix="PREFIX", testdir="tdir", verbosity=0, copy="mock")
86+
mock%installer_t = installer
87+
mock%os = OS_LINUX
88+
mock%expected_dir = "PREFIX/tdir"
89+
mock%expected_run = 'mock "name" "'//mock%expected_dir//'"'
90+
91+
call mock%install_test("name", error)
92+
93+
end subroutine test_install_tests_unix
94+
95+
subroutine test_install_tests_win(error)
96+
!> Error handling
97+
type(error_t), allocatable, intent(out) :: error
98+
99+
type(mock_installer_t) :: mock
100+
type(installer_t) :: installer
101+
102+
call new_installer(installer, prefix="PREFIX", testdir="tdir", verbosity=0, copy="mock")
103+
mock%installer_t = installer
104+
mock%os = OS_WINDOWS
105+
mock%expected_dir = "PREFIX\tdir"
106+
mock%expected_run = 'mock "name.exe" "'//mock%expected_dir//'"'
107+
108+
call mock%install_test("name", error)
109+
110+
end subroutine test_install_tests_win
111+
76112
subroutine test_install_lib(error)
77113
!> Error handling
78114
type(error_t), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)