From 9df74dbf3d9369592ea601ab726b1e5c1cf80e81 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 29 Nov 2020 00:21:22 +0100 Subject: Implement fpm-install command - allow installing of executables - optionally install library and modules if specified in manifest - add install table to manifest reference --- fpm/app/main.f90 | 3 +- fpm/src/fpm.f90 | 9 +-- fpm/src/fpm/cmd/install.f90 | 121 ++++++++++++++++++++++++++++ fpm/src/fpm/installer.f90 | 166 +++++++++++++++++++++++++++++++++++++++ fpm/src/fpm/manifest/install.f90 | 47 +++++++++++ fpm/src/fpm/manifest/package.f90 | 20 ++++- fpm/src/fpm_command_line.f90 | 57 +++++++++++--- fpm/src/fpm_environment.f90 | 12 +++ fpm/test/cli_test/cli_test.f90 | 5 +- manifest-reference.md | 16 ++++ 10 files changed, 433 insertions(+), 23 deletions(-) create mode 100644 fpm/src/fpm/cmd/install.f90 create mode 100644 fpm/src/fpm/installer.f90 create mode 100644 fpm/src/fpm/manifest/install.f90 diff --git a/fpm/app/main.f90 b/fpm/app/main.f90 index 0fe159b..7476df6 100644 --- a/fpm/app/main.f90 +++ b/fpm/app/main.f90 @@ -8,7 +8,8 @@ use fpm_command_line, only: & fpm_install_settings, & fpm_update_settings, & get_command_line_settings -use fpm, only: cmd_build, cmd_install, cmd_run +use fpm, only: cmd_build, cmd_run +use fpm_cmd_install, only: cmd_install use fpm_cmd_new, only: cmd_new use fpm_cmd_update, only : cmd_update diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 1b32cb6..79ced14 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -25,7 +25,8 @@ use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & use fpm_manifest_dependency, only: dependency_config_t implicit none private -public :: build_model, cmd_build, cmd_install, cmd_run +public :: cmd_build, cmd_run +public :: build_model contains @@ -204,12 +205,6 @@ endif end subroutine -subroutine cmd_install(settings) -type(fpm_install_settings), intent(in) :: settings - print *, "fpm error: 'fpm install' not implemented." - error stop 8 -end subroutine cmd_install - subroutine cmd_run(settings,test) class(fpm_run_settings), intent(in) :: settings logical, intent(in) :: test diff --git a/fpm/src/fpm/cmd/install.f90 b/fpm/src/fpm/cmd/install.f90 new file mode 100644 index 0000000..1c06d30 --- /dev/null +++ b/fpm/src/fpm/cmd/install.f90 @@ -0,0 +1,121 @@ +module fpm_cmd_install + use fpm, only : build_model + use fpm_backend, only : build_package + use fpm_command_line, only : fpm_install_settings + use fpm_error, only : error_t + 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, build_target_t, FPM_TARGET_EXECUTABLE, & + FPM_SCOPE_APP + use fpm_strings, only : string_t + implicit none + private + + public :: cmd_install + +contains + + !> Entry point for the fpm-install subcommand + subroutine cmd_install(settings) + !> Representation of the command line settings + type(fpm_install_settings), intent(in) :: settings + type(package_config_t) :: package + type(error_t), allocatable :: error + type(fpm_model_t) :: model + type(installer_t) :: installer + character(len=:), allocatable :: lib, exe, dir + + call get_package_data(package, "fpm.toml", error, apply_defaults=.true.) + call handle_error(error) + + call build_model(model, settings%fpm_build_settings, package, error) + call handle_error(error) + + if (.not.settings%no_rebuild) then + call build_package(model) + end if + + call new_installer(installer, prefix=settings%prefix, & + bindir=settings%bindir, libdir=settings%libdir, & + includedir=settings%includedir) + + if (allocated(package%library) .and. package%install%library) then + dir = join_path(model%output_directory, model%package_name) + lib = "lib"//model%package_name//".a" + call installer%install_library(join_path(dir, lib), error) + call handle_error(error) + + call install_module_files(installer, dir, error) + call handle_error(error) + end if + + if (allocated(package%executable)) then + call install_executables(installer, model, error) + call handle_error(error) + end if + + end subroutine cmd_install + + subroutine install_module_files(installer, dir, error) + type(installer_t), intent(inout) :: installer + character(len=*), intent(in) :: dir + type(error_t), allocatable, intent(out) :: error + type(string_t), allocatable :: modules(:) + integer :: ii + + call list_files(dir, modules, recurse=.false.) + + do ii = 1, size(modules) + if (is_module_file(modules(ii)%s)) then + call installer%install_header(modules(ii)%s, error) + if (allocated(error)) exit + end if + end do + if (allocated(error)) return + + end subroutine install_module_files + + subroutine install_executables(installer, model, error) + type(installer_t), intent(inout) :: installer + type(fpm_model_t), intent(in) :: model + type(error_t), allocatable, intent(out) :: error + integer :: ii + + do ii = 1, size(model%targets) + if (is_executable_target(model%targets(ii)%ptr)) then + call installer%install_executable(model%targets(ii)%ptr%output_file, error) + if (allocated(error)) exit + end if + end do + if (allocated(error)) return + + end subroutine install_executables + + elemental function is_executable_target(target_ptr) result(is_exe) + type(build_target_t), intent(in) :: target_ptr + logical :: is_exe + is_exe = target_ptr%target_type == FPM_TARGET_EXECUTABLE .and. & + allocated(target_ptr%dependencies) + if (is_exe) then + is_exe = target_ptr%dependencies(1)%ptr%source%unit_scope == FPM_SCOPE_APP + end if + end function is_executable_target + + elemental function is_module_file(name) result(is_mod) + character(len=*), intent(in) :: name + logical :: is_mod + integer :: ll + ll = len(name) + is_mod = name(max(1, ll-3):ll) == ".mod" + end function is_module_file + + subroutine handle_error(error) + type(error_t), intent(in), optional :: error + if (present(error)) then + print '(a)', error%message + error stop 1 + end if + end subroutine handle_error + +end module fpm_cmd_install diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 new file mode 100644 index 0000000..8c4235e --- /dev/null +++ b/fpm/src/fpm/installer.f90 @@ -0,0 +1,166 @@ +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 + implicit none + private + + public :: installer_t, new_installer + + + type :: installer_t + character(len=:), allocatable :: prefix + character(len=:), allocatable :: bindir + character(len=:), allocatable :: libdir + character(len=:), allocatable :: includedir + integer :: unit = output_unit + integer :: verbosity = 1 + character(len=:), allocatable :: copy + !> Cached operating system + integer :: os + contains + procedure :: install_executable + procedure :: install_library + procedure :: install_header + procedure :: install_source + procedure :: install + procedure :: run + procedure :: make_dir + end type installer_t + + character(len=*), parameter :: default_bindir = "bin" + character(len=*), parameter :: default_libdir = "lib" + character(len=*), parameter :: default_includedir = "include" + character(len=*), parameter :: default_prefix_unix = "/usr/local/bin" + character(len=*), parameter :: default_prefix_win = "C:\" + character(len=*), parameter :: default_copy_unix = "cp -v" + character(len=*), parameter :: default_copy_win = "copy" + +contains + + subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity) + type(installer_t), intent(out) :: self + character(len=*), intent(in), optional :: prefix + character(len=*), intent(in), optional :: bindir + character(len=*), intent(in), optional :: libdir + character(len=*), intent(in), optional :: includedir + integer, intent(in), optional :: verbosity + + self%os = get_os_type() + + if (os_is_unix(self%os)) then + self%copy = default_copy_unix + else + self%copy = default_copy_win + end if + + if (present(includedir)) then + self%includedir = includedir + else + self%includedir = default_includedir + end if + + if (present(prefix)) then + self%prefix = prefix + else + if (os_is_unix(self%os)) then + self%prefix = default_prefix_unix + else + self%prefix = default_prefix_win + end if + end if + + if (present(bindir)) then + self%bindir = bindir + else + self%bindir = default_bindir + end if + + if (present(libdir)) then + self%libdir = libdir + else + self%libdir = default_libdir + end if + + if (present(verbosity)) then + self%verbosity = verbosity + else + self%verbosity = 1 + end if + + end subroutine new_installer + + subroutine install_executable(self, executable, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: executable + type(error_t), allocatable, intent(out) :: error + + call self%install(executable, self%bindir, error) + end subroutine install_executable + + subroutine install_library(self, library, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: library + type(error_t), allocatable, intent(out) :: error + + call self%install(library, self%libdir, error) + end subroutine install_library + + subroutine install_header(self, header, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: header + type(error_t), allocatable, intent(out) :: error + + call self%install(header, self%includedir, error) + end subroutine install_header + + subroutine install_source(self, source, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: source + type(error_t), allocatable, intent(out) :: error + end subroutine install_source + + subroutine install(self, source, destination, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: source + character(len=*), intent(in) :: destination + type(error_t), allocatable, intent(out) :: error + + character(len=:), allocatable :: install_dest + + install_dest = join_path(self%prefix, destination) + call self%make_dir(install_dest, error) + if (allocated(error)) return + + if (os_is_unix(self%os)) then + call self%run(self%copy//" "//source//" "//install_dest, error) + else + call self%run(self%copy//" "//source//" "//install_dest, error) + end if + if (allocated(error)) return + + end subroutine install + + subroutine make_dir(self, dir, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: dir + type(error_t), allocatable, intent(out) :: error + if (.not.exists(dir)) call mkdir(dir) + end subroutine make_dir + + subroutine run(self, command, error) + class(installer_t), intent(inout) :: self + character(len=*), intent(in) :: command + type(error_t), allocatable, intent(out) :: error + integer :: stat + + call execute_command_line(command, exitstat=stat) + + if (stat /= 0) then + call fatal_error(error, "Failed in command: '"//command//"'") + return + end if + end subroutine run + +end module fpm_installer diff --git a/fpm/src/fpm/manifest/install.f90 b/fpm/src/fpm/manifest/install.f90 new file mode 100644 index 0000000..492aa9d --- /dev/null +++ b/fpm/src/fpm/manifest/install.f90 @@ -0,0 +1,47 @@ +module fpm_manifest_install + use fpm_error, only : error_t, fatal_error, syntax_error + use fpm_toml, only : toml_table, toml_key, toml_stat, get_value + implicit none + private + + public :: install_config_t, new_install_config + + type :: install_config_t + logical :: library + end type install_config_t + +contains + + subroutine new_install_config(self, table, error) + type(install_config_t), intent(out) :: self + type(toml_table), intent(inout) :: table + type(error_t), allocatable, intent(out) :: error + call check(table, error) + if (allocated(error)) return + + call get_value(table, "library", self%library, .false.) + + end subroutine new_install_config + + subroutine check(table, error) + type(toml_table), intent(inout) :: table + type(error_t), allocatable, intent(out) :: error + + type(toml_key), allocatable :: list(:) + integer :: ikey + call table%get_keys(list) + if (size(list) < 1) return + + do ikey = 1, size(list) + select case(list(ikey)%key) + case default + call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in package file") + exit + case("library") + continue + end select + end do + if (allocated(error)) return + end subroutine check + +end module fpm_manifest_install diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index 9c759a5..1215b41 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -24,6 +24,8 @@ !>[library] !>[dependencies] !>[dev-dependencies] +!>[build] +!>[install] !>[[ executable ]] !>[[ example ]] !>[[ test ]] @@ -34,6 +36,7 @@ module fpm_manifest_package use fpm_manifest_example, only : example_config_t, new_example use fpm_manifest_executable, only : executable_config_t, new_executable use fpm_manifest_library, only : library_config_t, new_library + use fpm_manifest_install, only: install_config_t, new_install_config use fpm_manifest_test, only : test_config_t, new_test use fpm_error, only : error_t, fatal_error, syntax_error use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, & @@ -57,11 +60,14 @@ module fpm_manifest_package !> Name of the package character(len=:), allocatable :: name + !> Package version + type(version_t) :: version + !> Build configuration data type(build_config_t) :: build - !> Package version - type(version_t) :: version + !> Installation configuration data + type(install_config_t) :: install !> Library meta data type(library_config_t), allocatable :: library @@ -139,12 +145,18 @@ contains return end if call new_build_config(self%build, child, error) + if (allocated(error)) return + call get_value(table, "install", child, requested=.true., stat=stat) + if (stat /= toml_stat%success) then + call fatal_error(error, "Type mismatch for install entry, must be a table") + return + end if + call new_install_config(self%install, child, error) if (allocated(error)) return call get_value(table, "version", version, "0") call new_version(self%version, version, error) - if (allocated(error)) return call get_value(table, "dependencies", child, requested=.false.) @@ -265,7 +277,7 @@ contains case("version", "license", "author", "maintainer", "copyright", & & "description", "keywords", "categories", "homepage", "build", & & "dependencies", "dev-dependencies", "test", "executable", & - & "example", "library") + & "example", "library", "install") continue end select diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 96a335f..b78906b 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -73,7 +73,12 @@ end type type, extends(fpm_run_settings) :: fpm_test_settings end type -type, extends(fpm_cmd_settings) :: fpm_install_settings +type, extends(fpm_build_settings) :: fpm_install_settings + character(len=:), allocatable :: prefix + character(len=:), allocatable :: bindir + character(len=:), allocatable :: libdir + character(len=:), allocatable :: includedir + logical :: no_rebuild end type !> Settings for interacting and updating with project dependencies @@ -106,6 +111,7 @@ contains character(len=4096) :: cmdarg integer :: i integer :: widest + type(fpm_install_settings), allocatable :: install_settings call set_help() ! text for --version switch, @@ -293,12 +299,24 @@ contains call printhelp(help_text) case('install') - call set_args('& - & --release F& - & --verbose F& - &', help_install, version_text) + call set_args('--release F --no-rebuild F --prefix " " & + & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & + & --libdir "lib" --bindir "bin" --includedir "include"', & + help_install, version_text) + + call check_build_vals() + + allocate(install_settings) + install_settings = fpm_install_settings(& + build_name=val_build,& + compiler=val_compiler, & + no_rebuild=lget('no-rebuild')) + call get_char_arg(install_settings%prefix, 'prefix') + call get_char_arg(install_settings%libdir, 'libdir') + call get_char_arg(install_settings%bindir, 'bindir') + call get_char_arg(install_settings%includedir, 'includedir') + call move_alloc(install_settings, cmd_settings) - allocate(fpm_install_settings :: cmd_settings) case('list') call set_args('& & --list F& @@ -893,10 +911,31 @@ contains ' The fpm(1) home page at https://github.com/fortran-lang/fpm', & '' ] help_install=[character(len=80) :: & - ' fpm(1) subcommand "install" ', & - ' ', & - ' fpm install NAME ', & + 'NAME', & + ' fpm-install(1) - install fpm projects', & + '', & + 'SYNOPSIS', & + ' fpm install [--release] [--no-rebuild] [--prefix DIR]', & + ' [--bindir DIR] [--libdir DIR] [--includedir DIR]', & + '', & + 'DESCRIPTION', & + ' Subcommand to install fpm projects.', & + '', & + 'OPTIONS', & + ' --release selects the optimized build instead of the debug build', & + ' --no-rebuild do not rebuild project before installation', & + ' --prefix DIR path to installation directory (requires write access)', & + ' --bindir DIR subdirectory to place executables in', & + ' --libdir DIR subdirectory to place libraries and archies in', & + ' --includedir DIR subdirectory to place headers and module files in', & '' ] end subroutine set_help + subroutine get_char_arg(var, arg) + character(len=:), allocatable, intent(out) :: var + character(len=*), intent(in) :: arg + var = sget(arg) + if (len_trim(var) == 0) deallocate(var) + end subroutine get_char_arg + end module fpm_command_line diff --git a/fpm/src/fpm_environment.f90 b/fpm/src/fpm_environment.f90 index 1a8afef..181252d 100644 --- a/fpm/src/fpm_environment.f90 +++ b/fpm/src/fpm_environment.f90 @@ -2,6 +2,7 @@ module fpm_environment implicit none private public :: get_os_type + public :: os_is_unix public :: run public :: get_env @@ -105,6 +106,17 @@ contains end if end function get_os_type + logical function os_is_unix(os) result(unix) + integer, intent(in), optional :: os + integer :: build_os + if (present(os)) then + build_os = os + else + build_os = get_os_type() + end if + unix = os /= OS_WINDOWS + end function os_is_unix + subroutine run(cmd) character(len=*), intent(in) :: cmd integer :: stat diff --git a/fpm/test/cli_test/cli_test.f90 b/fpm/test/cli_test/cli_test.f90 index fdb7979..c30d688 100644 --- a/fpm/test/cli_test/cli_test.f90 +++ b/fpm/test/cli_test/cli_test.f90 @@ -193,8 +193,9 @@ use fpm_command_line, only: & fpm_test_settings, & fpm_install_settings, & get_command_line_settings -use fpm, only: cmd_build, cmd_install, cmd_run -use fpm_cmd_new, only: cmd_new +use fpm, only: cmd_build, cmd_run +use fpm_cmd_install, only: cmd_install +use fpm_cmd_new, only: cmd_new class(fpm_cmd_settings), allocatable :: cmd_settings ! duplicates the calls as seen in the main program for fpm call get_command_line_settings(cmd_settings) diff --git a/manifest-reference.md b/manifest-reference.md index 45b4827..07235b9 100644 --- a/manifest-reference.md +++ b/manifest-reference.md @@ -45,6 +45,9 @@ Every manifest file consists of the following sections: Project library dependencies - [*dev-dependencies*](#development-dependencies): Dependencies only needed for tests +- [*install*](#installation-configuration): + Installation configuration + [TOML]: https://toml.io/ @@ -438,3 +441,16 @@ rev = "2f5eaba864ff630ba0c3791126a3f811b6e437f3" ### Development dependencies Development dependencies allow to declare *dev-dependencies* in the manifest root, which are available to all tests but not exported with the project. + + +## Installation configuration + +In the *install* section components for the installation can be selected. +By default only executables are installed, library projects can set the *library* boolean to also installatation the module files and the archive. + +*Example* + +```toml +[install] +library = true +``` -- cgit v1.2.3 From 4977652445ebecd595a32cf70ae3be56759ea57a Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 29 Nov 2020 12:45:14 +0100 Subject: Extend documentation and add tests for install configuration --- fpm/src/fpm/cmd/install.f90 | 3 +- fpm/src/fpm/installer.f90 | 324 ++++++++++++++++++++++-------------- fpm/src/fpm/manifest/install.f90 | 63 ++++++- fpm/src/fpm/manifest/package.f90 | 2 + fpm/src/fpm_command_line.f90 | 7 +- fpm/test/fpm_test/test_manifest.f90 | 70 +++++++- 6 files changed, 340 insertions(+), 129 deletions(-) diff --git a/fpm/src/fpm/cmd/install.f90 b/fpm/src/fpm/cmd/install.f90 index 1c06d30..0f620e9 100644 --- a/fpm/src/fpm/cmd/install.f90 +++ b/fpm/src/fpm/cmd/install.f90 @@ -38,7 +38,8 @@ contains call new_installer(installer, prefix=settings%prefix, & bindir=settings%bindir, libdir=settings%libdir, & - includedir=settings%includedir) + includedir=settings%includedir, & + verbosity=merge(2, 1, settings%verbose)) if (allocated(package%library) .and. package%install%library) then dir = join_path(model%output_directory, model%package_name) diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 index 8c4235e..5ef471b 100644 --- a/fpm/src/fpm/installer.f90 +++ b/fpm/src/fpm/installer.f90 @@ -1,3 +1,8 @@ +!> Implementation of an installer object. +!> +!> The installer provides a way to install objects to their respective directories +!> in the installation prefix, a generic install command allows to install +!> to any directory within the prefix. module fpm_installer use, intrinsic :: iso_fortran_env, only : output_unit use fpm_environment, only : get_os_type, os_is_unix @@ -9,158 +14,229 @@ module fpm_installer public :: installer_t, new_installer + !> Declaration of the installer type type :: installer_t + !> Path to installation directory character(len=:), allocatable :: prefix + !> Binary dir relative to the installation prefix character(len=:), allocatable :: bindir + !> Library directory relative to the installation prefix character(len=:), allocatable :: libdir + !> Include directory relative to the installation prefix character(len=:), allocatable :: includedir + !> Output unit for informative printout integer :: unit = output_unit + !> Verbosity of the installer integer :: verbosity = 1 + !> Command to copy objects into the installation prefix character(len=:), allocatable :: copy !> Cached operating system integer :: os contains + !> Install an executable in its correct subdirectory procedure :: install_executable + !> Install a library in its correct subdirectory procedure :: install_library + !> Install a header/module in its correct subdirectory procedure :: install_header - procedure :: install_source + !> Install a generic file into a subdirectory in the installation prefix procedure :: install + !> Run an installation command, type-bound for unit testing purposes procedure :: run + !> Create a new directory in the prefix, type-bound for unit testing purposes procedure :: make_dir end type installer_t + !> Default name of the binary subdirectory character(len=*), parameter :: default_bindir = "bin" + + !> Default name of the library subdirectory character(len=*), parameter :: default_libdir = "lib" + + !> Default name of the include subdirectory character(len=*), parameter :: default_includedir = "include" + + !> Default name of the installation prefix on Unix platforms character(len=*), parameter :: default_prefix_unix = "/usr/local/bin" + + !> Default name of the installation prefix on Windows platforms character(len=*), parameter :: default_prefix_win = "C:\" - character(len=*), parameter :: default_copy_unix = "cp -v" + + !> Copy command on Unix platforms + character(len=*), parameter :: default_copy_unix = "cp" + + !> Copy command on Windows platforms character(len=*), parameter :: default_copy_win = "copy" contains - subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity) - type(installer_t), intent(out) :: self - character(len=*), intent(in), optional :: prefix - character(len=*), intent(in), optional :: bindir - character(len=*), intent(in), optional :: libdir - character(len=*), intent(in), optional :: includedir - integer, intent(in), optional :: verbosity - - self%os = get_os_type() - - if (os_is_unix(self%os)) then - self%copy = default_copy_unix - else - self%copy = default_copy_win - end if - - if (present(includedir)) then - self%includedir = includedir - else - self%includedir = default_includedir - end if - - if (present(prefix)) then - self%prefix = prefix - else - if (os_is_unix(self%os)) then - self%prefix = default_prefix_unix - else - self%prefix = default_prefix_win + !> Create a new instance of an installer + subroutine new_installer(self, prefix, bindir, libdir, includedir, verbosity) + !> Instance of the installer + type(installer_t), intent(out) :: self + !> Path to installation directory + character(len=*), intent(in), optional :: prefix + !> Binary dir relative to the installation prefix + character(len=*), intent(in), optional :: bindir + !> Library directory relative to the installation prefix + character(len=*), intent(in), optional :: libdir + !> Include directory relative to the installation prefix + character(len=*), intent(in), optional :: includedir + !> Verbosity of the installer + integer, intent(in), optional :: verbosity + + self%os = get_os_type() + + if (os_is_unix(self%os)) then + self%copy = default_copy_unix + else + self%copy = default_copy_win + end if + + if (present(includedir)) then + self%includedir = includedir + else + self%includedir = default_includedir + end if + + if (present(prefix)) then + self%prefix = prefix + else + if (os_is_unix(self%os)) then + self%prefix = default_prefix_unix + else + self%prefix = default_prefix_win + end if + end if + + if (present(bindir)) then + self%bindir = bindir + else + self%bindir = default_bindir + end if + + if (present(libdir)) then + self%libdir = libdir + else + self%libdir = default_libdir + end if + + if (present(verbosity)) then + self%verbosity = verbosity + else + self%verbosity = 1 + end if + + end subroutine new_installer + + !> Install an executable in its correct subdirectory + subroutine install_executable(self, executable, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Path to the executable + character(len=*), intent(in) :: executable + !> Error handling + type(error_t), allocatable, intent(out) :: error + + call self%install(executable, self%bindir, error) + end subroutine install_executable + + !> Install a library in its correct subdirectory + subroutine install_library(self, library, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Path to the library + character(len=*), intent(in) :: library + !> Error handling + type(error_t), allocatable, intent(out) :: error + + call self%install(library, self%libdir, error) + end subroutine install_library + + !> Install a header/module in its correct subdirectory + subroutine install_header(self, header, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Path to the header + character(len=*), intent(in) :: header + !> Error handling + type(error_t), allocatable, intent(out) :: error + + call self%install(header, self%includedir, error) + end subroutine install_header + + !> Install a generic file into a subdirectory in the installation prefix + subroutine install(self, source, destination, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Path to the original file + character(len=*), intent(in) :: source + !> Path to the destination inside the prefix + character(len=*), intent(in) :: destination + !> Error handling + type(error_t), allocatable, intent(out) :: error + + character(len=:), allocatable :: install_dest + + install_dest = join_path(self%prefix, destination) + call self%make_dir(install_dest, error) + if (allocated(error)) return + + if (self%verbosity > 0) then + if (exists(install_dest)) then + write(self%unit, '("# Update:", 1x, a, 1x, "->", 1x, a)') & + source, install_dest + else + write(self%unit, '("# Install:", 1x, a, 1x, "->", 1x, a)') & + source, install_dest + end if + end if + + if (os_is_unix(self%os)) then + call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error) + else + call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error) + end if + if (allocated(error)) return + + end subroutine install + + !> Create a new directory in the prefix + subroutine make_dir(self, dir, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Directory to be created + character(len=*), intent(in) :: dir + !> Error handling + type(error_t), allocatable, intent(out) :: error + + if (.not.exists(dir)) then + if (self%verbosity > 1) then + write(self%unit, '("# Dir:", 1x, a)') dir end if - end if - - if (present(bindir)) then - self%bindir = bindir - else - self%bindir = default_bindir - end if - - if (present(libdir)) then - self%libdir = libdir - else - self%libdir = default_libdir - end if - - if (present(verbosity)) then - self%verbosity = verbosity - else - self%verbosity = 1 - end if - - end subroutine new_installer - - subroutine install_executable(self, executable, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: executable - type(error_t), allocatable, intent(out) :: error - - call self%install(executable, self%bindir, error) - end subroutine install_executable - - subroutine install_library(self, library, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: library - type(error_t), allocatable, intent(out) :: error - - call self%install(library, self%libdir, error) - end subroutine install_library - - subroutine install_header(self, header, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: header - type(error_t), allocatable, intent(out) :: error - - call self%install(header, self%includedir, error) - end subroutine install_header - - subroutine install_source(self, source, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: source - type(error_t), allocatable, intent(out) :: error - end subroutine install_source - - subroutine install(self, source, destination, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: source - character(len=*), intent(in) :: destination - type(error_t), allocatable, intent(out) :: error - - character(len=:), allocatable :: install_dest - - install_dest = join_path(self%prefix, destination) - call self%make_dir(install_dest, error) - if (allocated(error)) return - - if (os_is_unix(self%os)) then - call self%run(self%copy//" "//source//" "//install_dest, error) - else - call self%run(self%copy//" "//source//" "//install_dest, error) - end if - if (allocated(error)) return - - end subroutine install - - subroutine make_dir(self, dir, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: dir - type(error_t), allocatable, intent(out) :: error - if (.not.exists(dir)) call mkdir(dir) - end subroutine make_dir - - subroutine run(self, command, error) - class(installer_t), intent(inout) :: self - character(len=*), intent(in) :: command - type(error_t), allocatable, intent(out) :: error - integer :: stat - - call execute_command_line(command, exitstat=stat) - - if (stat /= 0) then - call fatal_error(error, "Failed in command: '"//command//"'") - return - end if - end subroutine run + call mkdir(dir) + end if + end subroutine make_dir + + !> Run an installation command + subroutine run(self, command, error) + !> Instance of the installer + class(installer_t), intent(inout) :: self + !> Command to be launched + character(len=*), intent(in) :: command + !> Error handling + type(error_t), allocatable, intent(out) :: error + integer :: stat + + if (self%verbosity > 1) then + write(self%unit, '("# Run:", 1x, a)') command + end if + call execute_command_line(command, exitstat=stat) + + if (stat /= 0) then + call fatal_error(error, "Failed in command: '"//command//"'") + return + end if + end subroutine run end module fpm_installer diff --git a/fpm/src/fpm/manifest/install.f90 b/fpm/src/fpm/manifest/install.f90 index 492aa9d..6175873 100644 --- a/fpm/src/fpm/manifest/install.f90 +++ b/fpm/src/fpm/manifest/install.f90 @@ -1,3 +1,10 @@ +!> Implementation of the installation configuration. +!> +!> An install table can currently have the following fields +!> +!>```toml +!>library = bool +!>``` module fpm_manifest_install use fpm_error, only : error_t, fatal_error, syntax_error use fpm_toml, only : toml_table, toml_key, toml_stat, get_value @@ -6,16 +13,33 @@ module fpm_manifest_install public :: install_config_t, new_install_config + !> Configuration data for installation type :: install_config_t + + !> Install library with this project logical :: library + + contains + + !> Print information on this instance + procedure :: info + end type install_config_t contains + !> Create a new installation configuration from a TOML data structure subroutine new_install_config(self, table, error) + + !> Instance of the install configuration type(install_config_t), intent(out) :: self + + !> Instance of the TOML data structure type(toml_table), intent(inout) :: table + + !> Error handling type(error_t), allocatable, intent(out) :: error + call check(table, error) if (allocated(error)) return @@ -23,25 +47,62 @@ contains end subroutine new_install_config + + !> Check local schema for allowed entries subroutine check(table, error) + + !> Instance of the TOML data structure type(toml_table), intent(inout) :: table + + !> Error handling type(error_t), allocatable, intent(out) :: error type(toml_key), allocatable :: list(:) integer :: ikey + call table%get_keys(list) if (size(list) < 1) return do ikey = 1, size(list) select case(list(ikey)%key) case default - call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in package file") + call syntax_error(error, "Key "//list(ikey)%key//" is not allowed in install table") exit case("library") continue end select end do if (allocated(error)) return + end subroutine check + !> Write information on install configuration instance + subroutine info(self, unit, verbosity) + + !> Instance of the build configuration + class(install_config_t), intent(in) :: self + + !> Unit for IO + integer, intent(in) :: unit + + !> Verbosity of the printout + integer, intent(in), optional :: verbosity + + integer :: pr + character(len=*), parameter :: fmt = '("#", 1x, a, t30, a)' + + if (present(verbosity)) then + pr = verbosity + else + pr = 1 + end if + + if (pr < 1) return + + write(unit, fmt) "Install configuration" + write(unit, fmt) " - library install", & + & trim(merge("enabled ", "disabled", self%library)) + + end subroutine info + end module fpm_manifest_install diff --git a/fpm/src/fpm/manifest/package.f90 b/fpm/src/fpm/manifest/package.f90 index 1215b41..bbaa51d 100644 --- a/fpm/src/fpm/manifest/package.f90 +++ b/fpm/src/fpm/manifest/package.f90 @@ -322,6 +322,8 @@ contains call self%build%info(unit, pr - 1) + call self%install%info(unit, pr - 1) + if (allocated(self%library)) then write(unit, fmt) "- target", "archive" call self%library%info(unit, pr - 1) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index b78906b..d56e9e1 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -299,7 +299,7 @@ contains call printhelp(help_text) case('install') - call set_args('--release F --no-rebuild F --prefix " " & + call set_args('--release F --no-rebuild F --verbose F --prefix " " & & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & & --libdir "lib" --bindir "bin" --includedir "include"', & help_install, version_text) @@ -310,7 +310,8 @@ contains install_settings = fpm_install_settings(& build_name=val_build,& compiler=val_compiler, & - no_rebuild=lget('no-rebuild')) + no_rebuild=lget('no-rebuild'), & + 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%bindir, 'bindir') @@ -917,6 +918,7 @@ contains 'SYNOPSIS', & ' fpm install [--release] [--no-rebuild] [--prefix DIR]', & ' [--bindir DIR] [--libdir DIR] [--includedir DIR]', & + ' [--verbose]', & '', & 'DESCRIPTION', & ' Subcommand to install fpm projects.', & @@ -928,6 +930,7 @@ contains ' --bindir DIR subdirectory to place executables in', & ' --libdir DIR subdirectory to place libraries and archies in', & ' --includedir DIR subdirectory to place headers and module files in', & + ' --verbose print more information', & '' ] end subroutine set_help diff --git a/fpm/test/fpm_test/test_manifest.f90 b/fpm/test/fpm_test/test_manifest.f90 index d8adf50..925eaf3 100644 --- a/fpm/test/fpm_test/test_manifest.f90 +++ b/fpm/test/fpm_test/test_manifest.f90 @@ -57,7 +57,10 @@ contains & new_unittest("link-array", test_link_array), & & new_unittest("link-error", test_invalid_link, should_fail=.true.), & & new_unittest("example-simple", test_example_simple), & - & new_unittest("example-empty", test_example_empty, should_fail=.true.)] + & new_unittest("example-empty", test_example_empty, should_fail=.true.), & + & new_unittest("install-library", test_install_library), & + & new_unittest("install-empty", test_install_empty), & + & new_unittest("install-wrongkey", test_install_wrongkey, should_fail=.true.)] end subroutine collect_manifest @@ -993,4 +996,69 @@ contains end subroutine test_invalid_link + subroutine test_install_library(error) + use fpm_manifest_install + use fpm_toml, only : toml_table, set_value + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(install_config_t) :: install + + table = toml_table() + call set_value(table, "library", .true.) + + call new_install_config(install, table, error) + if (allocated(error)) return + + if (.not.install%library) then + call test_failed(error, "Library entry should be true") + return + end if + + end subroutine test_install_library + + + subroutine test_install_empty(error) + use fpm_manifest_install + use fpm_toml, only : toml_table + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(install_config_t) :: install + + table = toml_table() + + call new_install_config(install, table, error) + if (allocated(error)) return + + if (install%library) then + call test_failed(error, "Library default should be false") + return + end if + + end subroutine test_install_empty + + + subroutine test_install_wrongkey(error) + use fpm_manifest_install + use fpm_toml, only : toml_table, set_value + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(toml_table) :: table + type(install_config_t) :: install + + table = toml_table() + call set_value(table, "prefix", "/some/install/path") + + call new_install_config(install, table, error) + + end subroutine test_install_wrongkey + + end module test_manifest -- cgit v1.2.3 From 738300b515d5e9a9630a3e4abed72d728bcdaa3b Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 29 Nov 2020 12:53:38 +0100 Subject: Let fpm install itself on CI-runs --- ci/run_tests.bat | 6 ++++++ ci/run_tests.sh | 10 +++++++++- fpm/src/fpm/installer.f90 | 10 ++++++++++ 3 files changed, 25 insertions(+), 1 deletion(-) diff --git a/ci/run_tests.bat b/ci/run_tests.bat index 42f391c..ef4a1f2 100755 --- a/ci/run_tests.bat +++ b/ci/run_tests.bat @@ -26,6 +26,12 @@ echo %fpm_path% %fpm_path% if errorlevel 1 exit 1 +%fpm_path% build +if errorlevel 1 exit 1 + +%fpm_path% install --prefix "%CD%\_dist" --no-rebuild +if errorlevel 1 exit 1 + cd ..\example_packages\hello_world if errorlevel 1 exit 1 diff --git a/ci/run_tests.sh b/ci/run_tests.sh index 7412fba..8229d54 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -15,12 +15,20 @@ rm -rf fpm_scratch_*/ fpm test $@ rm -rf fpm_scratch_*/ -# Build example packages f_fpm_path="$(fpm run $@ --runner echo)" + +# Let fpm build itself +"${f_fpm_path}" build + +# Install fpm into local directory +"${f_fpm_path}" install --prefix "$PWD/_dist" --no-rebuild + +# Build example packages cd ../example_packages/ rm -rf ./*/build cd hello_world + "${f_fpm_path}" build ./build/gfortran_debug/app/hello_world "${f_fpm_path}" run diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 index 5ef471b..1d2341c 100644 --- a/fpm/src/fpm/installer.f90 +++ b/fpm/src/fpm/installer.f90 @@ -137,8 +137,18 @@ contains character(len=*), intent(in) :: executable !> Error handling type(error_t), allocatable, intent(out) :: error + integer :: ll + + if (.not.os_is_unix(self%os)) then + ll = len(executable) + if (executable(max(1, ll-3):ll) /= ".exe") then + call self%install(executable//".exe", self%bindir, error) + return + end if + end if call self%install(executable, self%bindir, error) + end subroutine install_executable !> Install a library in its correct subdirectory -- cgit v1.2.3 From 7b4c601102232a012216c252c48f5616a9b208f6 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 29 Nov 2020 13:57:17 +0100 Subject: Add unit tests for installer command - abstract some platform specifics in the unit tests --- fpm/src/fpm/installer.f90 | 22 +++-- fpm/src/fpm_filesystem.f90 | 2 +- fpm/test/fpm_test/main.f90 | 2 + fpm/test/fpm_test/test_installer.f90 | 168 +++++++++++++++++++++++++++++++++++ 4 files changed, 188 insertions(+), 6 deletions(-) create mode 100644 fpm/test/fpm_test/test_installer.f90 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 -- cgit v1.2.3 From 342feaca1e968145b37b2cea05373788d0a79227 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Mon, 30 Nov 2020 18:37:08 +0100 Subject: Add fpm-install command to fpm-manual --- fpm/src/fpm/installer.f90 | 8 ++------ fpm/src/fpm_command_line.f90 | 13 +++++++++++-- fpm/test/help_test/help_test.f90 | 5 ++++- 3 files changed, 17 insertions(+), 9 deletions(-) diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 index 54b796d..ddfc77b 100644 --- a/fpm/src/fpm/installer.f90 +++ b/fpm/src/fpm/installer.f90 @@ -57,7 +57,7 @@ module fpm_installer character(len=*), parameter :: default_includedir = "include" !> Default name of the installation prefix on Unix platforms - character(len=*), parameter :: default_prefix_unix = "/usr/local/bin" + character(len=*), parameter :: default_prefix_unix = "/usr/local" !> Default name of the installation prefix on Windows platforms character(len=*), parameter :: default_prefix_win = "C:\" @@ -214,11 +214,7 @@ contains end if end if - if (os_is_unix(self%os)) then - call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error) - else - call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error) - end if + call self%run(self%copy//' "'//source//'" "'//install_dest//'"', error) if (allocated(error)) return end subroutine install diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index d56e9e1..af96fd9 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -100,7 +100,7 @@ character(len=:), allocatable :: help_new(:), help_fpm(:), help_run(:), & & help_list(:), help_list_dash(:), help_list_nodash(:) character(len=20),parameter :: manual(*)=[ character(len=20) ::& & ' ', 'fpm', 'new', 'build', 'run', & -& 'test', 'runner', 'update','list', 'help', 'version' ] +& 'test', 'runner', 'install', 'update', 'list', 'help', 'version' ] character(len=:), allocatable :: val_runner, val_build, val_compiler @@ -276,6 +276,8 @@ contains help_text=[character(len=widest) :: help_text, help_new] case('build ' ) help_text=[character(len=widest) :: help_text, help_build] + case('install' ) + help_text=[character(len=widest) :: help_text, help_install] case('run ' ) help_text=[character(len=widest) :: help_text, help_run] case('test ' ) @@ -578,6 +580,7 @@ contains ' + test Run the tests. ', & ' + help Alternate method for displaying subcommand help. ', & ' + list Display brief descriptions of all subcommands. ', & + ' + install Install project ', & ' ', & ' Their syntax is ', & ' ', & @@ -588,6 +591,7 @@ contains ' [--runner "CMD"] [--compiler COMPILER_NAME] [-- ARGS] ', & ' help [NAME(s)] ', & ' list [--list] ', & + ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', & ' ', & 'SUBCOMMAND OPTIONS ', & ' --release Builds or runs in release mode (versus debug mode). fpm(1)', & @@ -616,6 +620,7 @@ contains ' fpm run ', & ' fpm new --help ', & ' fpm run myprogram --release -- -x 10 -y 20 --title "my title" ', & + ' fpm install --prefix ~/.local ', & ' ', & 'SEE ALSO ', & ' ', & @@ -928,9 +933,13 @@ contains ' --no-rebuild do not rebuild project before installation', & ' --prefix DIR path to installation directory (requires write access)', & ' --bindir DIR subdirectory to place executables in', & - ' --libdir DIR subdirectory to place libraries and archies in', & + ' --libdir DIR subdirectory to place libraries and archives in', & ' --includedir DIR subdirectory to place headers and module files in', & ' --verbose print more information', & + '', & + 'EXAMPLES', & + ' Install release version of project:', & + ' fpm install --release --prefix ~/.local', & '' ] end subroutine set_help diff --git a/fpm/test/help_test/help_test.f90 b/fpm/test/help_test/help_test.f90 index eb452b1..b9c1645 100644 --- a/fpm/test/help_test/help_test.f90 +++ b/fpm/test/help_test/help_test.f90 @@ -27,6 +27,7 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: & 'fpm run -- help run >> fpm_scratch_help.txt',& 'fpm run -- help test >> fpm_scratch_help.txt',& 'fpm run -- help runner >> fpm_scratch_help.txt',& +'fpm run -- help install >> fpm_scratch_help.txt',& 'fpm run -- help list >> fpm_scratch_help.txt',& 'fpm run -- help help >> fpm_scratch_help.txt',& 'fpm run -- --version >> fpm_scratch_help.txt',& @@ -39,6 +40,7 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: & 'fpm run --release -- help run >> fpm_scratch_help3.txt',& 'fpm run --release -- help test >> fpm_scratch_help3.txt',& 'fpm run --release -- help runner >> fpm_scratch_help3.txt',& +'fpm run --release -- help install >> fpm_scratch_help3.txt',& 'fpm run --release -- help list >> fpm_scratch_help3.txt',& 'fpm run --release -- help help >> fpm_scratch_help3.txt',& 'fpm run --release -- --version >> fpm_scratch_help3.txt',& @@ -48,7 +50,8 @@ character(len=*),parameter :: cmds(*) = [character(len=80) :: & !'fpm run >> fpm_scratch_help.txt',& !'fpm run -- --list >> fpm_scratch_help.txt',& !'fpm run -- list --list >> fpm_scratch_help.txt',& -character(len=*),parameter :: names(*)=[character(len=10) :: 'fpm','new','update','build','run','test','runner','list','help'] +character(len=*),parameter :: names(*)=[character(len=10) ::& + 'fpm','new','update','build','run','test','runner','install','list','help'] character(len=:),allocatable :: add write(*,'(g0:,1x)')'TEST help SUBCOMMAND STARTED' -- cgit v1.2.3 From 8d7c5e8313fe348a4682af5877ca570ebd030343 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 6 Dec 2020 11:08:29 +0100 Subject: Try to use local install path with fallback to platform defaults - use $HOME/.local as user prefix on Unix platforms (fallback is /usr/local) - use %APPDATA%\local as user prefix on Windows (fallback is C:\) --- fpm/src/fpm/installer.f90 | 36 ++++++++++++++++++++++++++++++------ fpm/src/fpm_filesystem.f90 | 23 ++++++++++++++++++++++- 2 files changed, 52 insertions(+), 7 deletions(-) diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90 index ddfc77b..d01bd27 100644 --- a/fpm/src/fpm/installer.f90 +++ b/fpm/src/fpm/installer.f90 @@ -7,7 +7,8 @@ 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, unix_path, windows_path + use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path, & + env_variable implicit none private @@ -109,11 +110,7 @@ contains if (present(prefix)) then self%prefix = prefix else - if (os_is_unix(self%os)) then - self%prefix = default_prefix_unix - else - self%prefix = default_prefix_win - end if + call set_default_prefix(self%prefix, self%os) end if if (present(bindir)) then @@ -136,6 +133,33 @@ contains end subroutine new_installer + !> Set the default prefix for the installation + subroutine set_default_prefix(prefix, os) + !> Installation prefix + character(len=:), allocatable :: prefix + !> Platform identifier + integer, intent(in), optional :: os + + character(len=:), allocatable :: home + + if (os_is_unix(os)) then + call env_variable(home, "HOME") + if (allocated(home)) then + prefix = join_path(home, ".local") + else + prefix = default_prefix_unix + end if + else + call env_variable(home, "APPDATA") + if (allocated(home)) then + prefix = join_path(home, "local") + else + prefix = default_prefix_win + end if + end if + + end subroutine set_default_prefix + !> Install an executable in its correct subdirectory subroutine install_executable(self, executable, error) !> Instance of the installer diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90 index 433a75b..f221917 100644 --- a/fpm/src/fpm_filesystem.f90 +++ b/fpm/src/fpm_filesystem.f90 @@ -5,7 +5,7 @@ module fpm_filesystem use fpm_strings, only: f_string, string_t, split implicit none private - public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,& + public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, & mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file integer, parameter :: LINE_BUFFER_LEN = 1000 @@ -13,6 +13,27 @@ module fpm_filesystem contains +subroutine env_variable(var, name) + character(len=:), allocatable, intent(out) :: var + character(len=*), intent(in) :: name + integer :: length, stat + + call get_environment_variable(name, length=length, status=stat) + if (stat /= 0) return + + allocate(character(len=length) :: var) + + if (length > 0) then + call get_environment_variable(name, var, status=stat) + if (stat /= 0) then + deallocate(var) + return + end if + end if + +end subroutine env_variable + + function basename(path,suffix) result (base) ! Extract filename from path with/without suffix ! -- cgit v1.2.3 From 547805f21a5b9022eb7611e904319dec0eb48795 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 6 Dec 2020 14:29:56 +0100 Subject: Add fpm-install to fpm --list output - update documentation to include default settings --- fpm/src/fpm_command_line.f90 | 28 +++++++++++++++++++++++----- 1 file changed, 23 insertions(+), 5 deletions(-) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index af96fd9..a98f2c2 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -480,6 +480,7 @@ contains ' [--compiler COMPILER_NAME] [-- ARGS] ', & ' test [[--target] NAME(s)] [--release] [--runner "CMD"] [--list] ', & ' [--compiler COMPILER_NAME] [-- ARGS] ', & + ' install [--release] [--no-rebuild] [--prefix PATH] [options] ', & ' '] help_usage=[character(len=80) :: & '' ] @@ -926,20 +927,37 @@ contains ' [--verbose]', & '', & 'DESCRIPTION', & - ' Subcommand to install fpm projects.', & + ' Subcommand to install fpm projects. Running install will export the', & + ' current project to the selected prefix, this will by default install all', & + ' executables (test are excluded) which are part of the projects.', & + ' Libraries and module files are only installed for projects requiring the', & + ' installation of those components in the package manifest.', & '', & 'OPTIONS', & ' --release selects the optimized build instead of the debug build', & ' --no-rebuild do not rebuild project before installation', & - ' --prefix DIR path to installation directory (requires write access)', & - ' --bindir DIR subdirectory to place executables in', & + ' --prefix DIR path to installation directory (requires write access),', & + ' the default prefix on Unix systems is $HOME/.local', & + ' and %APPDATA%\local on Windows', & + ' --bindir DIR subdirectory to place executables in (default: bin)', & ' --libdir DIR subdirectory to place libraries and archives in', & + ' (default: lib)', & ' --includedir DIR subdirectory to place headers and module files in', & + ' (default: include)', & ' --verbose print more information', & '', & 'EXAMPLES', & - ' Install release version of project:', & - ' fpm install --release --prefix ~/.local', & + ' 1. Install release version of project:', & + '', & + ' fpm install --release', & + '', & + ' 2. Install the project without rebuilding the executables:', & + '', & + ' fpm install --no-rebuild', & + '', & + ' 3. Install executables to a custom prefix into the exe directory:', & + '', & + ' fpm install --prefix $PWD --bindir exe', & '' ] end subroutine set_help -- cgit v1.2.3 From 657318e635dca480555da7f6f74c67494c4f6848 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 13 Dec 2020 13:44:17 +0100 Subject: Add fpm-install to cli help page --- fpm/src/fpm_command_line.f90 | 1 + 1 file changed, 1 insertion(+) diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index a98f2c2..63b1249 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -465,6 +465,7 @@ contains ' run Run the local package application programs ', & ' test Run the test programs ', & ' update Update and manage project dependencies ', & + ' install Install project ', & ' ', & ' Enter "fpm --list" for a brief list of subcommand options. Enter ', & ' "fpm --help" or "fpm SUBCOMMAND --help" for detailed descriptions. ', & -- cgit v1.2.3 From 60d151fb4eb2380953b87e976cdc738b70706da4 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sun, 13 Dec 2020 17:56:22 +0100 Subject: Check if the package is actually installable for fpm-install --- fpm/src/fpm/cmd/install.f90 | 12 ++++++++++-- 1 file changed, 10 insertions(+), 2 deletions(-) diff --git a/fpm/src/fpm/cmd/install.f90 b/fpm/src/fpm/cmd/install.f90 index 0f620e9..41cfe43 100644 --- a/fpm/src/fpm/cmd/install.f90 +++ b/fpm/src/fpm/cmd/install.f90 @@ -2,7 +2,7 @@ module fpm_cmd_install use fpm, only : build_model use fpm_backend, only : build_package use fpm_command_line, only : fpm_install_settings - use fpm_error, only : error_t + use fpm_error, only : error_t, fatal_error 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 @@ -25,6 +25,7 @@ contains type(fpm_model_t) :: model type(installer_t) :: installer character(len=:), allocatable :: lib, exe, dir + logical :: installable call get_package_data(package, "fpm.toml", error, apply_defaults=.true.) call handle_error(error) @@ -32,6 +33,13 @@ contains call build_model(model, settings%fpm_build_settings, package, error) call handle_error(error) + installable = (allocated(package%library) .and. package%install%library) & + .or. allocated(package%executable) + if (.not.installable) then + call fatal_error(error, "Project does not contain any installable targets") + call handle_error(error) + end if + if (.not.settings%no_rebuild) then call build_package(model) end if @@ -114,7 +122,7 @@ contains subroutine handle_error(error) type(error_t), intent(in), optional :: error if (present(error)) then - print '(a)', error%message + print '("[Error]", 1x, a)', error%message error stop 1 end if end subroutine handle_error -- cgit v1.2.3 From 2fdd5dde77e84bfa9bd9f20e0bd2b47bdb65c18f Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Mon, 14 Dec 2020 19:02:09 +0100 Subject: Implement fpm install --list to see installable targets --- fpm/src/fpm/cmd/install.f90 | 42 +++++++++++++++++++++++++++++++++++++++++- fpm/src/fpm_command_line.f90 | 14 +++++++++----- fpm/src/fpm_strings.f90 | 39 +++++++++++++++++++++++++++++++++++++++ 3 files changed, 89 insertions(+), 6 deletions(-) diff --git a/fpm/src/fpm/cmd/install.f90 b/fpm/src/fpm/cmd/install.f90 index 41cfe43..59ba3a5 100644 --- a/fpm/src/fpm/cmd/install.f90 +++ b/fpm/src/fpm/cmd/install.f90 @@ -1,4 +1,5 @@ module fpm_cmd_install + use, intrinsic :: iso_fortran_env, only : output_unit use fpm, only : build_model use fpm_backend, only : build_package use fpm_command_line, only : fpm_install_settings @@ -8,7 +9,7 @@ module fpm_cmd_install use fpm_manifest, only : package_config_t, get_package_data use fpm_model, only : fpm_model_t, build_target_t, FPM_TARGET_EXECUTABLE, & FPM_SCOPE_APP - use fpm_strings, only : string_t + use fpm_strings, only : string_t, resize implicit none private @@ -40,6 +41,11 @@ contains call handle_error(error) end if + if (settings%list) then + call install_info(output_unit, package, model) + return + end if + if (.not.settings%no_rebuild) then call build_package(model) end if @@ -66,6 +72,40 @@ contains end subroutine cmd_install + subroutine install_info(unit, package, model) + integer, intent(in) :: unit + type(package_config_t), intent(in) :: package + type(fpm_model_t), intent(in) :: model + + integer :: ii, ntargets + character(len=:), allocatable :: lib + type(string_t), allocatable :: install_target(:) + + call resize(install_target) + + ntargets = 0 + if (allocated(package%library) .and. package%install%library) then + ntargets = ntargets + 1 + lib = join_path(model%output_directory, model%package_name, & + "lib"//model%package_name//".a") + install_target(ntargets)%s = lib + end if + do ii = 1, size(model%targets) + if (is_executable_target(model%targets(ii)%ptr)) then + if (ntargets >= size(install_target)) call resize(install_target) + ntargets = ntargets + 1 + install_target(ntargets)%s = model%targets(ii)%ptr%output_file + end if + end do + + write(unit, '("#", *(1x, g0))') & + "total number of installable targets:", ntargets + do ii = 1, ntargets + write(unit, '("-", *(1x, g0))') install_target(ii)%s + end do + + end subroutine install_info + subroutine install_module_files(installer, dir, error) type(installer_t), intent(inout) :: installer character(len=*), intent(in) :: dir diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 63b1249..20932b5 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -302,6 +302,7 @@ contains case('install') call set_args('--release F --no-rebuild F --verbose F --prefix " " & + & --list F & & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & & --libdir "lib" --bindir "bin" --includedir "include"', & help_install, version_text) @@ -310,7 +311,8 @@ contains allocate(install_settings) install_settings = fpm_install_settings(& - build_name=val_build,& + list=lget('list'), & + build_name=val_build, & compiler=val_compiler, & no_rebuild=lget('no-rebuild'), & verbose=lget('verbose')) @@ -901,7 +903,7 @@ contains '' ] help_update=[character(len=80) :: & 'NAME', & - ' fpm-update(1) - manage project dependencies', & + ' update(1) - manage project dependencies', & '', & 'SYNOPSIS', & ' fpm update [--fetch-only] [--clean] [--verbose] [NAME(s)]', & @@ -920,21 +922,23 @@ contains '' ] help_install=[character(len=80) :: & 'NAME', & - ' fpm-install(1) - install fpm projects', & + ' install(1) - install fpm projects', & '', & 'SYNOPSIS', & - ' fpm install [--release] [--no-rebuild] [--prefix DIR]', & + ' fpm install [--release] [--list] [--no-rebuild] [--prefix DIR]', & ' [--bindir DIR] [--libdir DIR] [--includedir DIR]', & ' [--verbose]', & '', & 'DESCRIPTION', & ' Subcommand to install fpm projects. Running install will export the', & ' current project to the selected prefix, this will by default install all', & - ' executables (test are excluded) which are part of the projects.', & + ' executables (test and examples are excluded) which are part of the projects.', & ' Libraries and module files are only installed for projects requiring the', & ' installation of those components in the package manifest.', & '', & 'OPTIONS', & + ' --list list all installable targets for this project,', & + ' but do not install any of them', & ' --release selects the optimized build instead of the debug build', & ' --no-rebuild do not rebuild project before installation', & ' --prefix DIR path to installation directory (requires write access),', & diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index 8a569cd..ea1db01 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -5,11 +5,16 @@ implicit none private public :: f_string, lower, split, str_ends_with, string_t public :: string_array_contains, string_cat, operator(.in.), fnv_1a +public :: resize type string_t character(len=:), allocatable :: s end type +interface resize + module procedure :: resize_string +end interface + interface operator(.in.) module procedure string_array_contains end interface @@ -288,5 +293,39 @@ subroutine split(input_line,array,delimiters,order,nulls) enddo end subroutine split +subroutine resize_string(list, n) + !> Instance of the array to be resized + type(string_t), allocatable, intent(inout) :: list(:) + !> Dimension of the final array size + integer, intent(in), optional :: n + + type(string_t), allocatable :: tmp(:) + integer :: this_size, new_size, i + integer, parameter :: initial_size = 16 + + if (allocated(list)) then + this_size = size(list, 1) + call move_alloc(list, tmp) + else + this_size = initial_size + end if + + if (present(n)) then + new_size = n + else + new_size = this_size + this_size/2 + 1 + end if + + allocate(list(new_size)) + + if (allocated(tmp)) then + this_size = min(size(tmp, 1), size(list, 1)) + do i = 1, this_size + call move_alloc(tmp(i)%s, list(i)%s) + end do + deallocate(tmp) + end if + +end subroutine resize_string end module fpm_strings -- cgit v1.2.3