Skip to content

Commit

Permalink
install test programs to testdir
Browse files Browse the repository at this point in the history
  • Loading branch information
perazz committed Sep 23, 2024
1 parent 6df75fb commit 9427dc4
Show file tree
Hide file tree
Showing 2 changed files with 54 additions and 4 deletions.
34 changes: 30 additions & 4 deletions src/fpm/cmd/install.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module fpm_cmd_install
use fpm_filesystem, only : join_path, list_files
use fpm_installer, only : installer_t, new_installer
use fpm_manifest, only : package_config_t, get_package_data
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP, FPM_SCOPE_TEST
use fpm_targets, only: targets_from_sources, build_target_t, &
build_target_ptr, FPM_TARGET_EXECUTABLE, &
filter_library_targets, filter_executable_targets, filter_modules
Expand All @@ -34,7 +34,7 @@ subroutine cmd_install(settings)

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
call handle_error(error)

call build_model(model, settings, package, error)
call handle_error(error)

Expand All @@ -57,7 +57,7 @@ subroutine cmd_install(settings)
end if

call new_installer(installer, prefix=settings%prefix, &
bindir=settings%bindir, libdir=settings%libdir, &
bindir=settings%bindir, libdir=settings%libdir, testdir=settings%testdir, &
includedir=settings%includedir, &
verbosity=merge(2, 1, settings%verbose))

Expand All @@ -72,12 +72,19 @@ subroutine cmd_install(settings)
call handle_error(error)
end if
end if

if (allocated(package%executable) .or. ntargets>0) then
call install_executables(installer, targets, error)
call handle_error(error)
end if

if (allocated(package%test) .and. (package%install%test .or. model%include_tests)) then

call install_tests(installer, targets, error)
call handle_error(error)

end if

end subroutine cmd_install

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

call filter_executable_targets(targets, FPM_SCOPE_TEST, temp)
install_target = [install_target, temp]

ntargets = size(install_target)

if (verbose) then
Expand Down Expand Up @@ -144,6 +154,22 @@ subroutine install_executables(installer, targets, error)

end subroutine install_executables

subroutine install_tests(installer, targets, error)
type(installer_t), intent(inout) :: installer
type(build_target_ptr), intent(in) :: targets(:)
type(error_t), allocatable, intent(out) :: error
integer :: ii

do ii = 1, size(targets)
if (targets(ii)%ptr%is_executable_target(FPM_SCOPE_TEST)) then
call installer%install_test(targets(ii)%ptr%output_file, error)
if (allocated(error)) exit
end if
end do
if (allocated(error)) return

end subroutine install_tests

subroutine handle_error(error)
type(error_t), intent(in), optional :: error
if (present(error)) then
Expand Down
24 changes: 24 additions & 0 deletions src/fpm/installer.f90
Original file line number Diff line number Diff line change
Expand Up @@ -42,6 +42,8 @@ module fpm_installer
procedure :: install_library
!> Install a header/module in its correct subdirectory
procedure :: install_header
!> Install a test program in its correct subdirectory
procedure :: install_test
!> Install a generic file into a subdirectory in the installation prefix
procedure :: install
!> Run an installation command, type-bound for unit testing purposes
Expand Down Expand Up @@ -199,6 +201,28 @@ subroutine install_library(self, library, error)
call self%install(library, self%libdir, error)
end subroutine install_library

!> Install a test program in its correct subdirectory
subroutine install_test(self, test, error)
!> Instance of the installer
class(installer_t), intent(inout) :: self
!> Path to the test executable
character(len=*), intent(in) :: test
!> Error handling
type(error_t), allocatable, intent(out) :: error
integer :: ll

if (.not.os_is_unix(self%os)) then
ll = len(test)
if (test(max(1, ll-3):ll) /= ".exe") then
call self%install(test//".exe", self%testdir, error)
return
end if
end if

call self%install(test, self%testdir, error)

end subroutine install_test

!> Install a header/module in its correct subdirectory
subroutine install_header(self, header, error)
!> Instance of the installer
Expand Down

0 comments on commit 9427dc4

Please sign in to comment.