diff --git a/src/fpm/cmd/install.f90 b/src/fpm/cmd/install.f90 index 8f39fc02a7..559cd81b55 100644 --- a/src/fpm/cmd/install.f90 +++ b/src/fpm/cmd/install.f90 @@ -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 @@ -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) @@ -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)) @@ -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) @@ -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 @@ -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 diff --git a/src/fpm/installer.f90 b/src/fpm/installer.f90 index 9fbe0948ae..7cfc93e77b 100644 --- a/src/fpm/installer.f90 +++ b/src/fpm/installer.f90 @@ -21,6 +21,8 @@ module fpm_installer character(len=:), allocatable :: bindir !> Library directory relative to the installation prefix character(len=:), allocatable :: libdir + !> Test program directory relative to the installation prefix + character(len=:), allocatable :: testdir !> Include directory relative to the installation prefix character(len=:), allocatable :: includedir !> Output unit for informative printout @@ -40,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 @@ -53,6 +57,9 @@ module fpm_installer !> Default name of the library subdirectory character(len=*), parameter :: default_libdir = "lib" + + !> Default name of the test subdirectory + character(len=*), parameter :: default_testdir = "test" !> Default name of the include subdirectory character(len=*), parameter :: default_includedir = "include" @@ -78,7 +85,7 @@ module fpm_installer contains !> Create a new instance of an installer - subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, & + subroutine new_installer(self, prefix, bindir, libdir, includedir, testdir, verbosity, & copy, move) !> Instance of the installer type(installer_t), intent(out) :: self @@ -90,6 +97,8 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, & character(len=*), intent(in), optional :: libdir !> Include directory relative to the installation prefix character(len=*), intent(in), optional :: includedir + !> Test directory relative to the installation prefix + character(len=*), intent(in), optional :: testdir !> Verbosity of the installer integer, intent(in), optional :: verbosity !> Copy command @@ -125,6 +134,12 @@ subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity, & else self%includedir = default_includedir end if + + if (present(testdir)) then + self%testdir = testdir + else + self%testdir = default_testdir + end if if (present(prefix)) then self%prefix = prefix @@ -186,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 diff --git a/src/fpm/manifest/install.f90 b/src/fpm/manifest/install.f90 index 88c3097eb0..342090a1b3 100644 --- a/src/fpm/manifest/install.f90 +++ b/src/fpm/manifest/install.f90 @@ -18,6 +18,9 @@ module fpm_manifest_install !> Install library with this project logical :: library = .false. + + !> Install tests with this project + logical :: test = .false. contains @@ -51,6 +54,7 @@ subroutine new_install_config(self, table, error) if (allocated(error)) return call get_value(table, "library", self%library, .false.) + call get_value(table, "test", self%test, .false.) end subroutine new_install_config @@ -75,8 +79,8 @@ subroutine check(table, error) case default call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in install table") exit - case("library") - continue + case("library","test") + continue end select end do if (allocated(error)) return @@ -107,8 +111,8 @@ subroutine info(self, unit, verbosity) if (pr < 1) return write(unit, fmt) "Install configuration" - write(unit, fmt) " - library install", & - & trim(merge("enabled ", "disabled", self%library)) + write(unit, fmt) " - library install", trim(merge("enabled ", "disabled", self%library)) + write(unit, fmt) " - test install", trim(merge("enabled ", "disabled", self%test)) end subroutine info @@ -121,6 +125,7 @@ logical function install_conf_same(this,that) select type (other=>that) type is (install_config_t) if (this%library.neqv.other%library) return + if (this%test.neqv.other%test) return class default ! Not the same type return @@ -144,6 +149,10 @@ subroutine dump_to_toml(self, table, error) type(error_t), allocatable, intent(out) :: error call set_value(table, "library", self%library, error, class_name) + if (allocated(error)) return + + call set_value(table, "test", self%test, error, class_name) + if (allocated(error)) return end subroutine dump_to_toml @@ -163,6 +172,8 @@ subroutine load_from_toml(self, table, error) call get_value(table, "library", self%library, error, class_name) if (allocated(error)) return + call get_value(table, "test", self%test, error, class_name) + if (allocated(error)) return end subroutine load_from_toml diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90 index b5655437ec..3f905deffa 100644 --- a/src/fpm_command_line.f90 +++ b/src/fpm_command_line.f90 @@ -108,6 +108,7 @@ module fpm_command_line character(len=:), allocatable :: prefix character(len=:), allocatable :: bindir character(len=:), allocatable :: libdir + character(len=:), allocatable :: testdir character(len=:), allocatable :: includedir logical :: no_rebuild end type @@ -533,8 +534,8 @@ subroutine get_command_line_settings(cmd_settings) case('install') call set_args(common_args // compiler_args // '& & --no-rebuild F --prefix " " & - & --list F & - & --libdir "lib" --bindir "bin" --includedir "include"', & + & --list F --test F & + & --libdir "lib" --bindir "bin" --testdir "test" --includedir "include"', & help_install, version_text) call check_build_vals() @@ -544,6 +545,7 @@ subroutine get_command_line_settings(cmd_settings) archiver = sget('archiver') allocate(install_settings, source=fpm_install_settings(& list=lget('list'), & + build_tests=lget('test'), & profile=val_profile,& prune=.not.lget('no-prune'), & compiler=val_compiler, & @@ -558,6 +560,7 @@ subroutine get_command_line_settings(cmd_settings) verbose=lget('verbose'))) call get_char_arg(install_settings%prefix, 'prefix') call get_char_arg(install_settings%libdir, 'libdir') + call get_char_arg(install_settings%testdir, 'testdir') call get_char_arg(install_settings%bindir, 'bindir') call get_char_arg(install_settings%includedir, 'includedir') call move_alloc(install_settings, cmd_settings) @@ -1418,6 +1421,7 @@ subroutine set_help() help_text_build_common,& help_text_flag, & ' --no-rebuild do not rebuild project before installation', & + ' --test also install test programs', & ' --prefix DIR path to installation directory (requires write access),', & ' the default prefix on Unix systems is $HOME/.local', & ' and %APPDATA%\local on Windows', & @@ -1426,6 +1430,7 @@ subroutine set_help() ' (default: lib)', & ' --includedir DIR subdirectory to place headers and module files in', & ' (default: include)', & + ' --testdir DIR subdirectory to place test programs in (default: test)', & ' --verbose print more information', & '', & help_text_environment, & @@ -1442,6 +1447,9 @@ subroutine set_help() ' 3. Install executables to a custom prefix into the exe directory:', & '', & ' fpm install --prefix $PWD --bindir exe', & + ' 4. Install executables and test programs into the same "exe" directory:', & + '', & + ' fpm install --prefix $PWD --test --bindir exe --testdir exe', & '' ] help_clean=[character(len=80) :: & 'NAME', & diff --git a/test/fpm_test/test_installer.f90 b/test/fpm_test/test_installer.f90 index 1235ba5bc2..d6cc444d8c 100644 --- a/test/fpm_test/test_installer.f90 +++ b/test/fpm_test/test_installer.f90 @@ -35,7 +35,9 @@ subroutine collect_installer(testsuite) & new_unittest("install-sitepackages", test_install_sitepackages), & & new_unittest("install-mod", test_install_mod), & & new_unittest("install-exe-unix", test_install_exe_unix), & - & new_unittest("install-exe-win", test_install_exe_win)] + & new_unittest("install-exe-win", test_install_exe_win), & + & new_unittest("install-test-unix", test_install_tests_unix), & + & new_unittest("install-test-win", test_install_tests_win)] end subroutine collect_installer @@ -73,6 +75,40 @@ subroutine test_install_exe_win(error) end subroutine test_install_exe_win + subroutine test_install_tests_unix(error) + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(mock_installer_t) :: mock + type(installer_t) :: installer + + call new_installer(installer, prefix="PREFIX", testdir="tdir", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_LINUX + mock%expected_dir = "PREFIX/tdir" + mock%expected_run = 'mock "name" "'//mock%expected_dir//'"' + + call mock%install_test("name", error) + + end subroutine test_install_tests_unix + + subroutine test_install_tests_win(error) + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(mock_installer_t) :: mock + type(installer_t) :: installer + + call new_installer(installer, prefix="PREFIX", testdir="tdir", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_WINDOWS + mock%expected_dir = "PREFIX\tdir" + mock%expected_run = 'mock "name.exe" "'//mock%expected_dir//'"' + + call mock%install_test("name", error) + + end subroutine test_install_tests_win + subroutine test_install_lib(error) !> Error handling type(error_t), allocatable, intent(out) :: error