15
15
! >
16
16
! > For more information, please read the documentation for the procedures:
17
17
! >
18
- ! > - `[[targets_from_sources ]]`
18
+ ! > - `[[build_target_list ]]`
19
19
! > - `[[resolve_module_dependencies]]`
20
20
! >
21
21
module fpm_targets
@@ -24,7 +24,7 @@ module fpm_targets
24
24
use fpm_model
25
25
use fpm_environment, only: get_os_type, OS_WINDOWS
26
26
use fpm_filesystem, only: dirname, join_path, canon_path
27
- use fpm_strings, only: string_t, operator (.in .)
27
+ use fpm_strings, only: string_t, operator (.in .), string_cat
28
28
implicit none
29
29
30
30
private
@@ -75,7 +75,13 @@ module fpm_targets
75
75
76
76
! > Objects needed to link this target
77
77
type (string_t), allocatable :: link_objects(:)
78
+
79
+ ! > Link flags for this build target
80
+ character (:), allocatable :: link_flags
78
81
82
+ ! > Compile flags for this build target
83
+ character (:), allocatable :: compile_flags
84
+
79
85
! > Flag set when first visited to check for circular dependencies
80
86
logical :: touched = .false.
81
87
@@ -96,6 +102,28 @@ module fpm_targets
96
102
97
103
contains
98
104
105
+ ! > High-level wrapper to generate build target information
106
+ subroutine targets_from_sources (targets ,model ,error )
107
+
108
+ ! > The generated list of build targets
109
+ type (build_target_ptr), intent (out ), allocatable :: targets(:)
110
+
111
+ ! > The package model from which to construct the target list
112
+ type (fpm_model_t), intent (inout ), target :: model
113
+
114
+ ! > Error structure
115
+ type (error_t), intent (out ), allocatable :: error
116
+
117
+ call build_target_list(targets,model)
118
+
119
+ call resolve_module_dependencies(targets,error)
120
+ if (allocated (error)) return
121
+
122
+ call resolve_target_linking(targets,model)
123
+
124
+ end subroutine targets_from_sources
125
+
126
+
99
127
! > Constructs a list of build targets from a list of source files
100
128
! >
101
129
! >### Source-target mapping
@@ -115,19 +143,14 @@ module fpm_targets
115
143
! > is a library, then the executable target has an additional dependency on the library
116
144
! > archive target.
117
145
! >
118
- ! > @note Inter-object dependencies based on modules used and provided are generated separately
119
- ! > in `[[resolve_module_dependencies]]` after all targets have been enumerated.
120
- subroutine targets_from_sources (targets ,model ,error )
146
+ subroutine build_target_list (targets ,model )
121
147
122
148
! > The generated list of build targets
123
149
type (build_target_ptr), intent (out ), allocatable :: targets(:)
124
150
125
151
! > The package model from which to construct the target list
126
152
type (fpm_model_t), intent (inout ), target :: model
127
153
128
- ! > Error structure
129
- type (error_t), intent (out ), allocatable :: error
130
-
131
154
integer :: i, j
132
155
character (:), allocatable :: xsuffix, exe_dir
133
156
type (build_target_t), pointer :: dep
@@ -207,21 +230,6 @@ subroutine targets_from_sources(targets,model,error)
207
230
208
231
end do
209
232
210
- if (allocated (model% link_libraries)) then
211
- do i = 1 , size (model% link_libraries)
212
- model% link_flags = model% link_flags // " -l" // model% link_libraries(i)% s
213
- end do
214
- end if
215
-
216
- if (targets(1 )% ptr% target_type == FPM_TARGET_ARCHIVE) then
217
- model% library_file = targets(1 )% ptr% output_file
218
- end if
219
-
220
- call resolve_module_dependencies(targets,error)
221
- if (allocated (error)) return
222
-
223
- call resolve_target_linking(targets)
224
-
225
233
contains
226
234
227
235
function get_object_name (source ) result(object_file)
@@ -248,7 +256,7 @@ function get_object_name(source) result(object_file)
248
256
249
257
end function get_object_name
250
258
251
- end subroutine targets_from_sources
259
+ end subroutine build_target_list
252
260
253
261
254
262
! > Allocate a new target and append to target list
@@ -411,29 +419,56 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
411
419
end function find_module_dependency
412
420
413
421
414
- ! > For libraries and executables, build a list of objects required for linking
422
+ ! > Construct the linker flags string for each target
423
+ ! > `target%link_flags` includes non-library objects and library flags
415
424
! >
416
- ! > stored in `target%link_objects`
417
- ! >
418
- subroutine resolve_target_linking (targets )
425
+ subroutine resolve_target_linking (targets , model )
419
426
type (build_target_ptr), intent (inout ), target :: targets(:)
427
+ type (fpm_model_t), intent (in ) :: model
420
428
421
429
integer :: i
430
+ character (:), allocatable :: global_link_flags
431
+
432
+ if (targets(1 )% ptr% target_type == FPM_TARGET_ARCHIVE) then
433
+ global_link_flags = targets(1 )% ptr% output_file
434
+ else
435
+ allocate (character (0 ) :: global_link_flags)
436
+ end if
437
+
438
+ if (allocated (model% link_libraries)) then
439
+ if (size (model% link_libraries) > 0 ) then
440
+ global_link_flags = global_link_flags // " -l" // string_cat(model% link_libraries," -l" )
441
+ end if
442
+ end if
422
443
423
444
do i= 1 ,size (targets)
424
445
425
446
associate(target = > targets(i)% ptr)
426
447
448
+ target % compile_flags = model% fortran_compile_flags
449
+
427
450
allocate (target % link_objects(0 ))
428
451
429
452
if (target % target_type == FPM_TARGET_ARCHIVE) then
430
453
431
454
call get_link_objects(target % link_objects,target ,is_exe= .false. )
432
455
456
+ allocate (character (0 ) :: target % link_flags)
457
+
433
458
else if (target % target_type == FPM_TARGET_EXECUTABLE) then
434
459
435
460
call get_link_objects(target % link_objects,target ,is_exe= .true. )
436
461
462
+ target % link_flags = string_cat(target % link_objects," " )
463
+
464
+ if (allocated (target % link_libraries)) then
465
+ if (size (target % link_libraries) > 0 ) then
466
+ target % link_flags = target % link_flags // " -l" // string_cat(target % link_libraries," -l" )
467
+ end if
468
+ end if
469
+
470
+ target % link_flags = target % link_flags// " " // global_link_flags
471
+
437
472
end if
438
473
439
474
end associate
0 commit comments