@@ -30,6 +30,7 @@ subroutine cmd_install(settings)
3030 type (installer_t) :: installer
3131 type (string_t), allocatable :: list(:)
3232 logical :: installable
33+ integer :: ntargets
3334
3435 call get_package_data(package, " fpm.toml" , error, apply_defaults= .true. )
3536 call handle_error(error)
@@ -40,18 +41,17 @@ subroutine cmd_install(settings)
4041 call targets_from_sources(targets, model, settings% prune, error)
4142 call handle_error(error)
4243
44+ call install_info(output_unit, settings% list, targets, ntargets)
45+ if (settings% list) return
46+
4347 installable = (allocated (package% library) .and. package% install% library) &
44- .or. allocated (package% executable)
48+ .or. allocated (package% executable) .or. ntargets> 0
49+
4550 if (.not. installable) then
4651 call fatal_error(error, " Project does not contain any installable targets" )
4752 call handle_error(error)
4853 end if
4954
50- if (settings% list) then
51- call install_info(output_unit, targets)
52- return
53- end if
54-
5555 if (.not. settings% no_rebuild) then
5656 call build_package(targets,model,verbose= settings% verbose)
5757 end if
@@ -73,18 +73,20 @@ subroutine cmd_install(settings)
7373 end if
7474 end if
7575
76- if (allocated (package% executable)) then
76+ if (allocated (package% executable) .or. ntargets > 0 ) then
7777 call install_executables(installer, targets, error)
7878 call handle_error(error)
7979 end if
8080
8181 end subroutine cmd_install
8282
83- subroutine install_info (unit , targets )
83+ subroutine install_info (unit , verbose , targets , ntargets )
8484 integer , intent (in ) :: unit
85+ logical , intent (in ) :: verbose
8586 type (build_target_ptr), intent (in ) :: targets(:)
87+ integer , intent (out ) :: ntargets
8688
87- integer :: ii, ntargets
89+ integer :: ii
8890 type (string_t), allocatable :: install_target(:), temp(:)
8991
9092 allocate (install_target(0 ))
@@ -96,12 +98,16 @@ subroutine install_info(unit, targets)
9698 install_target = [install_target, temp]
9799
98100 ntargets = size (install_target)
101+
102+ if (verbose) then
99103
100- write (unit, ' ("#", *(1x, g0))' ) &
101- " total number of installable targets:" , ntargets
102- do ii = 1 , ntargets
103- write (unit, ' ("-", *(1x, g0))' ) install_target(ii)% s
104- end do
104+ write (unit, ' ("#", *(1x, g0))' ) &
105+ " total number of installable targets:" , ntargets
106+ do ii = 1 , ntargets
107+ write (unit, ' ("-", *(1x, g0))' ) install_target(ii)% s
108+ end do
109+
110+ endif
105111
106112 end subroutine install_info
107113
@@ -129,7 +135,7 @@ subroutine install_executables(installer, targets, error)
129135 integer :: ii
130136
131137 do ii = 1 , size (targets)
132- if (is_executable_target( targets(ii)% ptr)) then
138+ if (targets(ii)% ptr% is_executable_target(FPM_SCOPE_APP )) then
133139 call installer% install_executable(targets(ii)% ptr% output_file, error)
134140 if (allocated (error)) exit
135141 end if
@@ -138,20 +144,10 @@ subroutine install_executables(installer, targets, error)
138144
139145 end subroutine install_executables
140146
141- elemental function is_executable_target (target_ptr ) result(is_exe)
142- type (build_target_t), intent (in ) :: target_ptr
143- logical :: is_exe
144- is_exe = target_ptr% target_type == FPM_TARGET_EXECUTABLE .and. &
145- allocated (target_ptr% dependencies)
146- if (is_exe) then
147- is_exe = target_ptr% dependencies(1 )% ptr% source% unit_scope == FPM_SCOPE_APP
148- end if
149- end function is_executable_target
150-
151147 subroutine handle_error (error )
152148 type (error_t), intent (in ), optional :: error
153149 if (present (error)) then
154- call fpm_stop(1 ,error% message)
150+ call fpm_stop(1 ,' *cmd_install* error: ' // error% message)
155151 end if
156152 end subroutine handle_error
157153
0 commit comments