aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/fpm/cmd/install.f9024
-rw-r--r--src/fpm_targets.f9025
2 files changed, 31 insertions, 18 deletions
diff --git a/src/fpm/cmd/install.f90 b/src/fpm/cmd/install.f90
index b4a5608..099a0e5 100644
--- a/src/fpm/cmd/install.f90
+++ b/src/fpm/cmd/install.f90
@@ -10,7 +10,7 @@ module fpm_cmd_install
use fpm_model, only : fpm_model_t, FPM_SCOPE_APP
use fpm_targets, only: targets_from_sources, build_target_t, &
build_target_ptr, FPM_TARGET_EXECUTABLE, &
- filter_library_targets, filter_executable_targets
+ filter_library_targets, filter_executable_targets, filter_modules
use fpm_strings, only : string_t, resize
implicit none
private
@@ -69,7 +69,7 @@ contains
call installer%install_library(list(1)%s, error)
call handle_error(error)
- call install_module_files(installer, dir, error)
+ call install_module_files(installer, targets, error)
call handle_error(error)
end if
end if
@@ -109,20 +109,18 @@ contains
end subroutine install_info
- subroutine install_module_files(installer, dir, error)
+ subroutine install_module_files(installer, targets, error)
type(installer_t), intent(inout) :: installer
- character(len=*), intent(in) :: dir
+ type(build_target_ptr), intent(in) :: targets(:)
type(error_t), allocatable, intent(out) :: error
type(string_t), allocatable :: modules(:)
integer :: ii
- call list_files(dir, modules, recurse=.false.)
+ call filter_modules(targets, modules)
do ii = 1, size(modules)
- if (is_module_file(modules(ii)%s)) then
- call installer%install_header(modules(ii)%s, error)
- if (allocated(error)) exit
- end if
+ call installer%install_header(modules(ii)%s//".mod", error)
+ if (allocated(error)) exit
end do
if (allocated(error)) return
@@ -154,14 +152,6 @@ contains
end if
end function is_executable_target
- elemental function is_module_file(name) result(is_mod)
- character(len=*), intent(in) :: name
- logical :: is_mod
- integer :: ll
- ll = len(name)
- is_mod = name(max(1, ll-3):ll) == ".mod"
- end function is_module_file
-
subroutine handle_error(error)
type(error_t), intent(in), optional :: error
if (present(error)) then
diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90
index 788a5ce..87809e6 100644
--- a/src/fpm_targets.f90
+++ b/src/fpm_targets.f90
@@ -40,7 +40,7 @@ public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
public build_target_t, build_target_ptr
public targets_from_sources, resolve_module_dependencies
public resolve_target_linking, add_target, add_dependency
-public filter_library_targets, filter_executable_targets
+public filter_library_targets, filter_executable_targets, filter_modules
@@ -678,4 +678,27 @@ elemental function is_executable_target(target_ptr, scope) result(is_exe)
end function is_executable_target
+subroutine filter_modules(targets, list)
+ type(build_target_ptr), intent(in) :: targets(:)
+ type(string_t), allocatable, intent(out) :: list(:)
+
+ integer :: i, j, n
+
+ n = 0
+ call resize(list)
+ do i = 1, size(targets)
+ associate(target => targets(i)%ptr)
+ if (.not.allocated(target%source)) cycle
+ if (n + size(target%source%modules_provided) >= size(list)) call resize(list)
+ do j = 1, size(target%source%modules_provided)
+ n = n + 1
+ list(n)%s = join_path(target%output_dir, "fpm", &
+ target%source%modules_provided(j)%s)
+ end do
+ end associate
+ end do
+ call resize(list, n)
+end subroutine filter_modules
+
+
end module fpm_targets