diff options
-rw-r--r-- | fpm/src/fpm/installer.f90 | 22 | ||||
-rw-r--r-- | fpm/src/fpm_filesystem.f90 | 2 | ||||
-rw-r--r-- | fpm/test/fpm_test/main.f90 | 2 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_installer.f90 | 168 |
4 files changed, 188 insertions, 6 deletions
diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 index 1d2341c..54b796d 100644 --- a/fpm/src/fpm/installer.f90 +++ b/fpm/src/fpm/installer.f90 @@ -7,7 +7,7 @@ module fpm_installer use, intrinsic :: iso_fortran_env, only : output_unit use fpm_environment, only : get_os_type, os_is_unix use fpm_error, only : error_t, fatal_error - use fpm_filesystem, only : join_path, mkdir, exists + use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path implicit none private @@ -71,7 +71,8 @@ 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, verbosity, & + copy) !> Instance of the installer type(installer_t), intent(out) :: self !> Path to installation directory @@ -84,13 +85,19 @@ contains character(len=*), intent(in), optional :: includedir !> Verbosity of the installer integer, intent(in), optional :: verbosity + !> Copy command + character(len=*), intent(in), optional :: copy self%os = get_os_type() - if (os_is_unix(self%os)) then - self%copy = default_copy_unix + if (present(copy)) then + self%copy = copy else - self%copy = default_copy_win + if (os_is_unix(self%os)) then + self%copy = default_copy_unix + else + self%copy = default_copy_win + end if end if if (present(includedir)) then @@ -189,6 +196,11 @@ contains character(len=:), allocatable :: install_dest install_dest = join_path(self%prefix, destination) + if (os_is_unix(self%os)) then + install_dest = unix_path(install_dest) + else + install_dest = windows_path(install_dest) + end if call self%make_dir(install_dest, error) if (allocated(error)) return diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 8f89243..433a75b 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -6,7 +6,7 @@ module fpm_filesystem implicit none private public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,& - mkdir, exists, get_temp_filename, windows_path, getline, delete_file + mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file integer, parameter :: LINE_BUFFER_LEN = 1000 diff --git a/fpm/test/fpm_test/main.f90 b/fpm/test/fpm_test/main.f90 index bc81dc1..a7f4979 100644 --- a/fpm/test/fpm_test/main.f90 +++ b/fpm/test/fpm_test/main.f90 @@ -9,6 +9,7 @@ program fpm_testing use test_module_dependencies, only : collect_module_dependencies use test_package_dependencies, only : collect_package_dependencies use test_backend, only: collect_backend + use test_installer, only : collect_installer use test_versioning, only : collect_versioning implicit none integer :: stat, is @@ -25,6 +26,7 @@ program fpm_testing & new_testsuite("fpm_module_dependencies", collect_module_dependencies), & & new_testsuite("fpm_package_dependencies", collect_package_dependencies), & & new_testsuite("fpm_test_backend", collect_backend), & + & new_testsuite("fpm_installer", collect_installer), & & new_testsuite("fpm_versioning", collect_versioning) & & ] diff --git a/fpm/test/fpm_test/test_installer.f90 b/fpm/test/fpm_test/test_installer.f90 new file mode 100644 index 0000000..1235ba5 --- /dev/null +++ b/fpm/test/fpm_test/test_installer.f90 @@ -0,0 +1,168 @@ +!> Define tests for the `fpm_installer` module +!> +!> The tests here setup a mock environment to allow testing for Unix and Windows +!> platforms at the same time. +module test_installer + use testsuite, only : new_unittest, unittest_t, error_t, test_failed, & + & check_string + use fpm_environment, only : OS_WINDOWS, OS_LINUX + use fpm_filesystem, only : join_path + use fpm_installer + implicit none + private + + public :: collect_installer + + + type, extends(installer_t) :: mock_installer_t + character(len=:), allocatable :: expected_dir + character(len=:), allocatable :: expected_run + contains + procedure :: make_dir + procedure :: run + end type mock_installer_t + +contains + + !> Collect all exported unit tests + subroutine collect_installer(testsuite) + !> Collection of tests + type(unittest_t), allocatable, intent(out) :: testsuite(:) + + testsuite = [ & + & new_unittest("install-lib", test_install_lib), & + & new_unittest("install-pkgconfig", test_install_pkgconfig), & + & 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)] + + end subroutine collect_installer + + subroutine test_install_exe_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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_LINUX + mock%expected_dir = "PREFIX/bin" + mock%expected_run = 'mock "name" "'//mock%expected_dir//'"' + + call mock%install_executable("name", error) + + end subroutine test_install_exe_unix + + subroutine test_install_exe_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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_WINDOWS + mock%expected_dir = "PREFIX\bin" + mock%expected_run = 'mock "name.exe" "'//mock%expected_dir//'"' + + call mock%install_executable("name", error) + + end subroutine test_install_exe_win + + subroutine test_install_lib(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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%expected_dir = join_path("PREFIX", "lib") + mock%expected_run = 'mock "name" "'//join_path("PREFIX", "lib")//'"' + + call mock%install_library("name", error) + + end subroutine test_install_lib + + subroutine test_install_pkgconfig(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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_WINDOWS + mock%expected_dir = "PREFIX\lib\pkgconfig" + mock%expected_run = 'mock "name" "'//mock%expected_dir//'"' + + call mock%install("name", "lib/pkgconfig", error) + + end subroutine test_install_pkgconfig + + subroutine test_install_sitepackages(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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%os = OS_LINUX + mock%expected_dir = "PREFIX/lib/python3.7/site-packages" + mock%expected_run = 'mock "name" "'//mock%expected_dir//'"' + + call mock%install("name", join_path("lib", "python3.7", "site-packages"), & + error) + + end subroutine test_install_sitepackages + + subroutine test_install_mod(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", verbosity=0, copy="mock") + mock%installer_t = installer + mock%expected_dir = join_path("PREFIX", "include") + mock%expected_run = 'mock "name" "'//join_path("PREFIX", "include")//'"' + + call mock%install_header("name", error) + + end subroutine test_install_mod + + !> Create a new directory in the prefix + subroutine make_dir(self, dir, error) + !> Instance of the installer + class(mock_installer_t), intent(inout) :: self + !> Directory to be created + character(len=*), intent(in) :: dir + !> Error handling + type(error_t), allocatable, intent(out) :: error + + call check_string(error, self%expected_dir, dir, "dir") + + end subroutine make_dir + + !> Run an installation command + subroutine run(self, command, error) + !> Instance of the installer + class(mock_installer_t), intent(inout) :: self + !> Command to be launched + character(len=*), intent(in) :: command + !> Error handling + type(error_t), allocatable, intent(out) :: error + + call check_string(error, self%expected_run, command, "run") + end subroutine run + +end module test_installer |