@@ -259,60 +259,81 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
259
259
end function find_module_dependency
260
260
261
261
262
- ! > For link targets, enumerate any dependency objects required for linking
262
+ ! > For libraries and executables, build a list of objects required for linking
263
+ ! >
264
+ ! > stored in `target%link_objects`
265
+ ! >
263
266
subroutine resolve_target_linking (targets )
264
267
type (build_target_ptr), intent (inout ), target :: targets(:)
265
268
266
- integer :: i,j,k
267
- type (string_t) :: link_object
269
+ integer :: i
268
270
269
271
do i= 1 ,size (targets)
270
272
271
273
associate(target = > targets(i)% ptr)
272
274
273
275
allocate (target % link_objects(0 ))
274
276
275
- do j= 1 ,size (target % dependencies)
276
-
277
- if (target % target_type == FPM_TARGET_ARCHIVE ) then
278
-
279
- ! Construct object list for archive
280
- link_object% s = target % dependencies(j)% ptr% output_file
281
- target % link_objects = [target % link_objects, link_object]
282
-
283
- else if (target % target_type == FPM_TARGET_EXECUTABLE .and. &
284
- target % dependencies(j)% ptr% target_type == FPM_TARGET_OBJECT) then
285
-
286
- associate(exe_obj = > target % dependencies(j)% ptr)
287
-
288
- ! Construct object list for executable
289
- link_object% s = exe_obj% output_file
290
- target % link_objects = [target % link_objects, link_object]
291
-
292
- ! Include non-library object dependencies
293
- do k= 1 ,size (exe_obj% dependencies)
294
-
295
- if (allocated (exe_obj% dependencies(k)% ptr% source)) then
296
- if (exe_obj% dependencies(k)% ptr% source% unit_scope == &
297
- exe_obj% source% unit_scope) then
277
+ if (target % target_type == FPM_TARGET_ARCHIVE) then
298
278
299
- link_object% s = exe_obj% dependencies(k)% ptr% output_file
300
- target % link_objects = [target % link_objects, link_object]
279
+ call get_link_objects(target % link_objects,target ,is_exe= .false. )
301
280
302
- end if
303
- end if
304
-
305
- end do
281
+ else if (target % target_type == FPM_TARGET_EXECUTABLE) then
306
282
307
- end associate
308
-
309
- end if
283
+ call get_link_objects( target % link_objects, target ,is_exe = .true. )
284
+
285
+ end if
310
286
311
- end do
312
287
end associate
313
288
314
289
end do
315
290
291
+ contains
292
+
293
+ ! > Wrapper to build link object list
294
+ ! >
295
+ ! > For libraries: just list dependency objects of lib target
296
+ ! >
297
+ ! > For executables: need to recursively discover non-library
298
+ ! > dependency objects. (i.e. modules in same dir as program)
299
+ ! >
300
+ recursive subroutine get_link_objects (link_objects ,target ,is_exe )
301
+ type (string_t), intent (inout ), allocatable :: link_objects(:)
302
+ type (build_target_t), intent (in ) :: target
303
+ logical , intent (in ) :: is_exe
304
+
305
+ integer :: i
306
+ type (string_t) :: temp_str
307
+
308
+ if (.not. allocated (target % dependencies)) return
309
+
310
+ do i= 1 ,size (target % dependencies)
311
+
312
+ associate(dep = > target % dependencies(i)% ptr)
313
+
314
+ if (.not. allocated (dep% source)) cycle
315
+
316
+ ! Skip library dependencies for executable targets
317
+ ! since the library archive will always be linked
318
+ if (is_exe.and. (dep% source% unit_scope == FPM_SCOPE_LIB)) cycle
319
+
320
+ ! Skip if dependency object already listed
321
+ if (dep% output_file .in . link_objects) cycle
322
+
323
+ ! Add dependency object file to link object list
324
+ temp_str% s = dep% output_file
325
+ link_objects = [link_objects, temp_str]
326
+
327
+ ! For executable objects, also need to include non-library
328
+ ! dependencies from dependencies (recurse)
329
+ if (is_exe) call get_link_objects(link_objects,dep,is_exe= .true. )
330
+
331
+ end associate
332
+
333
+ end do
334
+
335
+ end subroutine get_link_objects
336
+
316
337
end subroutine resolve_target_linking
317
338
318
339
0 commit comments