Skip to content

Commit 4c34457

Browse files
authored
Fix fpm install with non-main.f90 auto executables (#1036)
2 parents 88ebb0a + 024fe94 commit 4c34457

File tree

8 files changed

+48
-36
lines changed

8 files changed

+48
-36
lines changed

ci/run_tests.sh

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -73,6 +73,12 @@ test ! -x ./build/gfortran_*/app/unused
7373
test ! -x ./build/gfortran_*/test/unused_test
7474
popd
7575

76+
pushd auto_with_nondefault_main
77+
"$fpm" build
78+
"$fpm" install --prefix=./installed
79+
test -x ./installed/bin/non_default_name
80+
popd
81+
7682
pushd tree_shake
7783
"$fpm" build
7884
"$fpm" run
Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
build/*
2+
installed/*
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
# auto_with_nondefault_main
2+
Install auto-executable with non-default source name
3+
fpm install --prefix=/path/to/install
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
program main
2+
print *, 'hello, world!'
3+
end program main
Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
name = "auto_with_nondefault_main"
2+
[build]
3+
auto-executables = true
4+
[library]
5+

src/fpm.f90

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -765,17 +765,11 @@ logical function should_be_run(settings,run_scope,exe_target)
765765

766766
integer :: j
767767

768-
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
769-
allocated(exe_target%dependencies)) then
768+
if (exe_target%is_executable_target(run_scope)) then
770769

771770
associate(exe_source => exe_target%dependencies(1)%ptr%source)
772771

773-
if (exe_source%unit_scope/=run_scope) then
774-
775-
! Other scope
776-
should_be_run = .false.
777-
778-
elseif (size(settings%name) == 0 .or. .not.settings%list) then
772+
if (size(settings%name) == 0 .or. .not.settings%list) then
779773

780774
! No list of targets
781775
should_be_run = .true.

src/fpm/cmd/install.f90

Lines changed: 22 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -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

src/fpm_targets.f90

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -132,6 +132,10 @@ module fpm_targets
132132

133133
!> Version number
134134
character(:), allocatable :: version
135+
136+
contains
137+
138+
procedure :: is_executable_target
135139

136140
end type build_target_t
137141

@@ -1043,7 +1047,7 @@ end subroutine filter_executable_targets
10431047

10441048

10451049
elemental function is_executable_target(target_ptr, scope) result(is_exe)
1046-
type(build_target_t), intent(in) :: target_ptr
1050+
class(build_target_t), intent(in) :: target_ptr
10471051
integer, intent(in) :: scope
10481052
logical :: is_exe
10491053
is_exe = target_ptr%target_type == FPM_TARGET_EXECUTABLE .and. &
@@ -1101,5 +1105,4 @@ function get_feature_flags(compiler, features) result(flags)
11011105
end if
11021106
end function get_feature_flags
11031107

1104-
11051108
end module fpm_targets

0 commit comments

Comments
 (0)