@@ -35,7 +35,8 @@ module fpm_targets
35
35
private
36
36
37
37
public FPM_TARGET_UNKNOWN, FPM_TARGET_EXECUTABLE, &
38
- FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT
38
+ FPM_TARGET_ARCHIVE, FPM_TARGET_OBJECT, &
39
+ FPM_TARGET_C_OBJECT
39
40
public build_target_t, build_target_ptr
40
41
public targets_from_sources, resolve_module_dependencies
41
42
public resolve_target_linking, add_target, add_dependency
@@ -50,7 +51,8 @@ module fpm_targets
50
51
integer , parameter :: FPM_TARGET_ARCHIVE = 2
51
52
! > Target type is compiled object
52
53
integer , parameter :: FPM_TARGET_OBJECT = 3
53
-
54
+ ! > Target type is c compiled object
55
+ integer , parameter :: FPM_TARGET_C_OBJECT = 4
54
56
55
57
! > Wrapper type for constructing arrays of `[[build_target_t]]` pointers
56
58
type build_target_ptr
@@ -121,7 +123,7 @@ subroutine targets_from_sources(targets,model,error)
121
123
122
124
call build_target_list(targets,model)
123
125
124
- call resolve_module_dependencies(targets,error)
126
+ call resolve_module_dependencies(targets,model % external_modules, error)
125
127
if (allocated (error)) return
126
128
127
129
call resolve_target_linking(targets,model)
@@ -194,7 +196,8 @@ subroutine build_target_list(targets,model)
194
196
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
195
197
196
198
call add_target(targets,source = sources(i), &
197
- type = FPM_TARGET_OBJECT,&
199
+ type = merge (FPM_TARGET_C_OBJECT,FPM_TARGET_OBJECT,&
200
+ sources(i)% unit_type== FPM_UNIT_CSOURCE), &
198
201
output_file = get_object_name(sources(i)))
199
202
200
203
if (with_lib .and. sources(i)% unit_scope == FPM_SCOPE_LIB) then
@@ -345,8 +348,9 @@ end subroutine add_dependency
345
348
! > a source file in the package of the correct scope, then a __fatal error__
346
349
! > is returned by the procedure and model construction fails.
347
350
! >
348
- subroutine resolve_module_dependencies (targets ,error )
351
+ subroutine resolve_module_dependencies (targets ,external_modules , error )
349
352
type (build_target_ptr), intent (inout ), target :: targets(:)
353
+ type (string_t), intent (in ) :: external_modules(:)
350
354
type (error_t), allocatable , intent (out ) :: error
351
355
352
356
type (build_target_ptr) :: dep
@@ -364,6 +368,11 @@ subroutine resolve_module_dependencies(targets,error)
364
368
cycle
365
369
end if
366
370
371
+ if (targets(i)% ptr% source% modules_used(j)% s .in . external_modules) then
372
+ ! Dependency satisfied in system-installed module
373
+ cycle
374
+ end if
375
+
367
376
if (any (targets(i)% ptr% source% unit_scope == &
368
377
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
369
378
dep% ptr = > &
@@ -442,7 +451,7 @@ subroutine resolve_target_linking(targets, model)
442
451
443
452
integer :: i
444
453
character (:), allocatable :: global_link_flags
445
- character (:), allocatable :: global_compile_flags
454
+ character (:), allocatable :: global_include_flags
446
455
447
456
if (size (targets) == 0 ) return
448
457
@@ -452,17 +461,16 @@ subroutine resolve_target_linking(targets, model)
452
461
allocate (character (0 ) :: global_link_flags)
453
462
end if
454
463
455
- global_compile_flags = model% fortran_compile_flags
456
-
457
464
if (allocated (model% link_libraries)) then
458
465
if (size (model% link_libraries) > 0 ) then
459
466
global_link_flags = global_link_flags // " -l" // string_cat(model% link_libraries," -l" )
460
467
end if
461
468
end if
462
469
470
+ allocate (character (0 ) :: global_include_flags)
463
471
if (allocated (model% include_dirs)) then
464
472
if (size (model% include_dirs) > 0 ) then
465
- global_compile_flags = global_compile_flags // &
473
+ global_include_flags = global_include_flags // &
466
474
& " -I" // string_cat(model% include_dirs," -I" )
467
475
end if
468
476
end if
@@ -471,7 +479,11 @@ subroutine resolve_target_linking(targets, model)
471
479
472
480
associate(target = > targets(i)% ptr)
473
481
474
- target % compile_flags = global_compile_flags
482
+ if (target % target_type /= FPM_TARGET_C_OBJECT) then
483
+ target % compile_flags = model% fortran_compile_flags// " " // global_include_flags
484
+ else
485
+ target % compile_flags = global_include_flags
486
+ end if
475
487
476
488
allocate (target % link_objects(0 ))
477
489
0 commit comments