Skip to content

Commit 6f816ad

Browse files
committed
Correctly install modulefiles from build targets
1 parent e90eee7 commit 6f816ad

File tree

2 files changed

+31
-18
lines changed

2 files changed

+31
-18
lines changed

src/fpm/cmd/install.f90

+7-17
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module fpm_cmd_install
1010
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
1111
use fpm_targets, only: targets_from_sources, build_target_t, &
1212
build_target_ptr, FPM_TARGET_EXECUTABLE, &
13-
filter_library_targets, filter_executable_targets
13+
filter_library_targets, filter_executable_targets, filter_modules
1414
use fpm_strings, only : string_t, resize
1515
implicit none
1616
private
@@ -69,7 +69,7 @@ subroutine cmd_install(settings)
6969
call installer%install_library(list(1)%s, error)
7070
call handle_error(error)
7171

72-
call install_module_files(installer, dir, error)
72+
call install_module_files(installer, targets, error)
7373
call handle_error(error)
7474
end if
7575
end if
@@ -109,20 +109,18 @@ subroutine install_info(unit, package, model, targets)
109109

110110
end subroutine install_info
111111

112-
subroutine install_module_files(installer, dir, error)
112+
subroutine install_module_files(installer, targets, error)
113113
type(installer_t), intent(inout) :: installer
114-
character(len=*), intent(in) :: dir
114+
type(build_target_ptr), intent(in) :: targets(:)
115115
type(error_t), allocatable, intent(out) :: error
116116
type(string_t), allocatable :: modules(:)
117117
integer :: ii
118118

119-
call list_files(dir, modules, recurse=.false.)
119+
call filter_modules(targets, modules)
120120

121121
do ii = 1, size(modules)
122-
if (is_module_file(modules(ii)%s)) then
123-
call installer%install_header(modules(ii)%s, error)
124-
if (allocated(error)) exit
125-
end if
122+
call installer%install_header(modules(ii)%s//".mod", error)
123+
if (allocated(error)) exit
126124
end do
127125
if (allocated(error)) return
128126

@@ -154,14 +152,6 @@ elemental function is_executable_target(target_ptr) result(is_exe)
154152
end if
155153
end function is_executable_target
156154

157-
elemental function is_module_file(name) result(is_mod)
158-
character(len=*), intent(in) :: name
159-
logical :: is_mod
160-
integer :: ll
161-
ll = len(name)
162-
is_mod = name(max(1, ll-3):ll) == ".mod"
163-
end function is_module_file
164-
165155
subroutine handle_error(error)
166156
type(error_t), intent(in), optional :: error
167157
if (present(error)) then

src/fpm_targets.f90

+24-1
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ module fpm_targets
4040
public build_target_t, build_target_ptr
4141
public targets_from_sources, resolve_module_dependencies
4242
public resolve_target_linking, add_target, add_dependency
43-
public filter_library_targets, filter_executable_targets
43+
public filter_library_targets, filter_executable_targets, filter_modules
4444

4545

4646

@@ -678,4 +678,27 @@ elemental function is_executable_target(target_ptr, scope) result(is_exe)
678678
end function is_executable_target
679679

680680

681+
subroutine filter_modules(targets, list)
682+
type(build_target_ptr), intent(in) :: targets(:)
683+
type(string_t), allocatable, intent(out) :: list(:)
684+
685+
integer :: i, j, n
686+
687+
n = 0
688+
call resize(list)
689+
do i = 1, size(targets)
690+
associate(target => targets(i)%ptr)
691+
if (.not.allocated(target%source)) cycle
692+
if (n + size(target%source%modules_provided) >= size(list)) call resize(list)
693+
do j = 1, size(target%source%modules_provided)
694+
n = n + 1
695+
list(n)%s = join_path(target%output_dir, "fpm", &
696+
target%source%modules_provided(j)%s)
697+
end do
698+
end associate
699+
end do
700+
call resize(list, n)
701+
end subroutine filter_modules
702+
703+
681704
end module fpm_targets

0 commit comments

Comments
 (0)