Skip to content

Commit 2fdd5dd

Browse files
committed
Implement fpm install --list to see installable targets
1 parent 60d151f commit 2fdd5dd

File tree

3 files changed

+89
-6
lines changed

3 files changed

+89
-6
lines changed

fpm/src/fpm/cmd/install.f90

Lines changed: 41 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
module fpm_cmd_install
2+
use, intrinsic :: iso_fortran_env, only : output_unit
23
use fpm, only : build_model
34
use fpm_backend, only : build_package
45
use fpm_command_line, only : fpm_install_settings
@@ -8,7 +9,7 @@ module fpm_cmd_install
89
use fpm_manifest, only : package_config_t, get_package_data
910
use fpm_model, only : fpm_model_t, build_target_t, FPM_TARGET_EXECUTABLE, &
1011
FPM_SCOPE_APP
11-
use fpm_strings, only : string_t
12+
use fpm_strings, only : string_t, resize
1213
implicit none
1314
private
1415

@@ -40,6 +41,11 @@ subroutine cmd_install(settings)
4041
call handle_error(error)
4142
end if
4243

44+
if (settings%list) then
45+
call install_info(output_unit, package, model)
46+
return
47+
end if
48+
4349
if (.not.settings%no_rebuild) then
4450
call build_package(model)
4551
end if
@@ -66,6 +72,40 @@ subroutine cmd_install(settings)
6672

6773
end subroutine cmd_install
6874

75+
subroutine install_info(unit, package, model)
76+
integer, intent(in) :: unit
77+
type(package_config_t), intent(in) :: package
78+
type(fpm_model_t), intent(in) :: model
79+
80+
integer :: ii, ntargets
81+
character(len=:), allocatable :: lib
82+
type(string_t), allocatable :: install_target(:)
83+
84+
call resize(install_target)
85+
86+
ntargets = 0
87+
if (allocated(package%library) .and. package%install%library) then
88+
ntargets = ntargets + 1
89+
lib = join_path(model%output_directory, model%package_name, &
90+
"lib"//model%package_name//".a")
91+
install_target(ntargets)%s = lib
92+
end if
93+
do ii = 1, size(model%targets)
94+
if (is_executable_target(model%targets(ii)%ptr)) then
95+
if (ntargets >= size(install_target)) call resize(install_target)
96+
ntargets = ntargets + 1
97+
install_target(ntargets)%s = model%targets(ii)%ptr%output_file
98+
end if
99+
end do
100+
101+
write(unit, '("#", *(1x, g0))') &
102+
"total number of installable targets:", ntargets
103+
do ii = 1, ntargets
104+
write(unit, '("-", *(1x, g0))') install_target(ii)%s
105+
end do
106+
107+
end subroutine install_info
108+
69109
subroutine install_module_files(installer, dir, error)
70110
type(installer_t), intent(inout) :: installer
71111
character(len=*), intent(in) :: dir

fpm/src/fpm_command_line.f90

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -302,6 +302,7 @@ subroutine get_command_line_settings(cmd_settings)
302302

303303
case('install')
304304
call set_args('--release F --no-rebuild F --verbose F --prefix " " &
305+
& --list F &
305306
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
306307
& --libdir "lib" --bindir "bin" --includedir "include"', &
307308
help_install, version_text)
@@ -310,7 +311,8 @@ subroutine get_command_line_settings(cmd_settings)
310311

311312
allocate(install_settings)
312313
install_settings = fpm_install_settings(&
313-
build_name=val_build,&
314+
list=lget('list'), &
315+
build_name=val_build, &
314316
compiler=val_compiler, &
315317
no_rebuild=lget('no-rebuild'), &
316318
verbose=lget('verbose'))
@@ -901,7 +903,7 @@ subroutine set_help()
901903
'' ]
902904
help_update=[character(len=80) :: &
903905
'NAME', &
904-
' fpm-update(1) - manage project dependencies', &
906+
' update(1) - manage project dependencies', &
905907
'', &
906908
'SYNOPSIS', &
907909
' fpm update [--fetch-only] [--clean] [--verbose] [NAME(s)]', &
@@ -920,21 +922,23 @@ subroutine set_help()
920922
'' ]
921923
help_install=[character(len=80) :: &
922924
'NAME', &
923-
' fpm-install(1) - install fpm projects', &
925+
' install(1) - install fpm projects', &
924926
'', &
925927
'SYNOPSIS', &
926-
' fpm install [--release] [--no-rebuild] [--prefix DIR]', &
928+
' fpm install [--release] [--list] [--no-rebuild] [--prefix DIR]', &
927929
' [--bindir DIR] [--libdir DIR] [--includedir DIR]', &
928930
' [--verbose]', &
929931
'', &
930932
'DESCRIPTION', &
931933
' Subcommand to install fpm projects. Running install will export the', &
932934
' current project to the selected prefix, this will by default install all', &
933-
' executables (test are excluded) which are part of the projects.', &
935+
' executables (test and examples are excluded) which are part of the projects.', &
934936
' Libraries and module files are only installed for projects requiring the', &
935937
' installation of those components in the package manifest.', &
936938
'', &
937939
'OPTIONS', &
940+
' --list list all installable targets for this project,', &
941+
' but do not install any of them', &
938942
' --release selects the optimized build instead of the debug build', &
939943
' --no-rebuild do not rebuild project before installation', &
940944
' --prefix DIR path to installation directory (requires write access),', &

fpm/src/fpm_strings.f90

Lines changed: 39 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -5,11 +5,16 @@ module fpm_strings
55
private
66
public :: f_string, lower, split, str_ends_with, string_t
77
public :: string_array_contains, string_cat, operator(.in.), fnv_1a
8+
public :: resize
89

910
type string_t
1011
character(len=:), allocatable :: s
1112
end type
1213

14+
interface resize
15+
module procedure :: resize_string
16+
end interface
17+
1318
interface operator(.in.)
1419
module procedure string_array_contains
1520
end interface
@@ -288,5 +293,39 @@ subroutine split(input_line,array,delimiters,order,nulls)
288293
enddo
289294
end subroutine split
290295

296+
subroutine resize_string(list, n)
297+
!> Instance of the array to be resized
298+
type(string_t), allocatable, intent(inout) :: list(:)
299+
!> Dimension of the final array size
300+
integer, intent(in), optional :: n
301+
302+
type(string_t), allocatable :: tmp(:)
303+
integer :: this_size, new_size, i
304+
integer, parameter :: initial_size = 16
305+
306+
if (allocated(list)) then
307+
this_size = size(list, 1)
308+
call move_alloc(list, tmp)
309+
else
310+
this_size = initial_size
311+
end if
312+
313+
if (present(n)) then
314+
new_size = n
315+
else
316+
new_size = this_size + this_size/2 + 1
317+
end if
318+
319+
allocate(list(new_size))
320+
321+
if (allocated(tmp)) then
322+
this_size = min(size(tmp, 1), size(list, 1))
323+
do i = 1, this_size
324+
call move_alloc(tmp(i)%s, list(i)%s)
325+
end do
326+
deallocate(tmp)
327+
end if
328+
329+
end subroutine resize_string
291330

292331
end module fpm_strings

0 commit comments

Comments
 (0)