Skip to content

Commit 9427dc4

Browse files
committed
install test programs to testdir
1 parent 6df75fb commit 9427dc4

File tree

2 files changed

+54
-4
lines changed

2 files changed

+54
-4
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: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,8 @@ module fpm_installer
4242
procedure :: install_library
4343
!> Install a header/module in its correct subdirectory
4444
procedure :: install_header
45+
!> Install a test program in its correct subdirectory
46+
procedure :: install_test
4547
!> Install a generic file into a subdirectory in the installation prefix
4648
procedure :: install
4749
!> Run an installation command, type-bound for unit testing purposes
@@ -199,6 +201,28 @@ subroutine install_library(self, library, error)
199201
call self%install(library, self%libdir, error)
200202
end subroutine install_library
201203

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+
202226
!> Install a header/module in its correct subdirectory
203227
subroutine install_header(self, header, error)
204228
!> Instance of the installer

0 commit comments

Comments
 (0)