@@ -148,6 +148,8 @@ subroutine targets_from_sources(targets,model,prune,error)
148148
149149 call build_target_list(targets,model)
150150
151+ call collect_exe_link_dependencies(targets)
152+
151153 call resolve_module_dependencies(targets,model% external_modules,error)
152154 if (allocated (error)) return
153155
@@ -334,6 +336,57 @@ end function get_object_name
334336end subroutine build_target_list
335337
336338
339+ ! > Add non-library non-module dependencies for executable targets
340+ ! >
341+ ! > Executable targets will link to any non-program non-module source files that
342+ ! > are in the same directory or in a subdirectory.
343+ ! >
344+ ! > (Note: Fortran module dependencies are handled separately in
345+ ! > `resolve_module_dependencies` and `resolve_target_linking`.)
346+ ! >
347+ subroutine collect_exe_link_dependencies (targets )
348+ type (build_target_ptr), intent (inout ) :: targets(:)
349+
350+ integer :: i, j
351+ character (:), allocatable :: exe_source_dir
352+
353+ ! Add non-module dependencies for executables
354+ do j= 1 ,size (targets)
355+
356+ if (targets(j)% ptr% target_type == FPM_TARGET_EXECUTABLE) then
357+
358+ do i= 1 ,size (targets)
359+
360+ if (i == j) cycle
361+
362+ associate(exe = > targets(j)% ptr, dep = > targets(i)% ptr)
363+
364+ exe_source_dir = dirname(exe% dependencies(1 )% ptr% source% file_name)
365+
366+ if (allocated (dep% source)) then
367+
368+ if (dep% source% unit_scope /= FPM_SCOPE_LIB .and. &
369+ dep% source% unit_type /= FPM_UNIT_PROGRAM .and. &
370+ dep% source% unit_type /= FPM_UNIT_MODULE .and. &
371+ index (dirname(dep% source% file_name), exe_source_dir) == 1 ) then
372+
373+ call add_dependency(exe, dep)
374+
375+ end if
376+
377+ end if
378+
379+ end associate
380+
381+ end do
382+
383+ end if
384+
385+ end do
386+
387+ end subroutine collect_exe_link_dependencies
388+
389+
337390! > Allocate a new target and append to target list
338391subroutine add_target (targets ,package ,type ,output_name ,source ,link_libraries , macros , version )
339392 type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
0 commit comments