aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/app/main.f903
-rw-r--r--fpm/src/fpm.f909
-rw-r--r--fpm/src/fpm/cmd/install.f90121
-rw-r--r--fpm/src/fpm/installer.f90166
-rw-r--r--fpm/src/fpm/manifest/install.f9047
-rw-r--r--fpm/src/fpm/manifest/package.f9020
-rw-r--r--fpm/src/fpm_command_line.f9057
-rw-r--r--fpm/src/fpm_environment.f9012
-rw-r--r--fpm/test/cli_test/cli_test.f905
-rw-r--r--manifest-reference.md16
10 files changed, 433 insertions, 23 deletions
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" ', &
- ' ', &
- '<USAGE> 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
+```