aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm/cmd/install.f9042
-rw-r--r--fpm/src/fpm_command_line.f9014
-rw-r--r--fpm/src/fpm_strings.f9039
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