Add dependencies to source-based targets (FPM_TARGET_OBJECT
)
based on any modules used by the corresponding source file.
Source files are assigned a scope of either FPM_SCOPE_LIB
,
FPM_SCOPE_APP
or FPM_SCOPE_TEST
. The scope controls which
modules may be used by the source file:
Library sources (FPM_SCOPE_LIB
) may only use modules
also with library scope. This includes library modules
from dependencies.
Executable sources (FPM_SCOPE_APP
,FPM_SCOPE_TEST
) may use
library modules (including dependencies) as well as any modules
corresponding to source files in the same directory or a
subdirectory of the executable source file.
If a module used by a source file cannot be resolved to a source file in the package of the correct scope, then a fatal error is returned by the procedure and model construction fails.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(build_target_ptr), | intent(inout), | target | :: | targets(:) | ||
type(string_t), | intent(in) | :: | external_modules(:) | |||
type(error_t), | intent(out), | allocatable | :: | error |
subroutine resolve_module_dependencies(targets,external_modules,error)
type(build_target_ptr), intent(inout), target :: targets(:)
type(string_t), intent(in) :: external_modules(:)
type(error_t), allocatable, intent(out) :: error
type(build_target_ptr) :: dep
integer :: i, j
do i=1,size(targets)
if (.not.allocated(targets(i)%ptr%source)) cycle
do j=1,size(targets(i)%ptr%source%modules_used)
if (targets(i)%ptr%source%modules_used(j)%s .in. targets(i)%ptr%source%modules_provided) then
! Dependency satisfied in same file, skip
cycle
end if
if (targets(i)%ptr%source%modules_used(j)%s .in. external_modules) then
! Dependency satisfied in system-installed module
cycle
end if
if (any(targets(i)%ptr%source%unit_scope == &
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
dep%ptr => &
find_module_dependency(targets,targets(i)%ptr%source%modules_used(j)%s, &
include_dir = dirname(targets(i)%ptr%source%file_name))
else
dep%ptr => &
find_module_dependency(targets,targets(i)%ptr%source%modules_used(j)%s)
end if
if (.not.associated(dep%ptr)) then
call fatal_error(error, &
'Unable to find source for module dependency: "' // &
targets(i)%ptr%source%modules_used(j)%s // &
'" used by "'//targets(i)%ptr%source%file_name//'"')
return
end if
call add_dependency(targets(i)%ptr, dep%ptr)
end do
end do
end subroutine resolve_module_dependencies