1
1
! ># Build target handling
2
2
! >
3
3
! > This module handles the construction of the build target list
4
- ! > from the sources list (`[[targets_from_sources]]`), the
4
+ ! > from the sources list (`[[targets_from_sources]]`), the
5
5
! > resolution of module-dependencies between build targets
6
6
! > (`[[resolve_module_dependencies]]`), and the enumeration of
7
7
! > objects required for link targets (`[[resolve_target_linking]]`).
8
8
! >
9
9
! > A build target (`[[build_target_t]]`) is a file to be generated
10
10
! > by the backend (compilation and linking).
11
- ! >
11
+ ! >
12
12
! > @note The current implementation is ignorant to the existence of
13
13
! > module files (`.mod`,`.smod`). Dependencies arising from modules
14
14
! > are based on the corresponding object files (`.o`) only.
@@ -83,13 +83,13 @@ module fpm_targets
83
83
84
84
! > Link flags for this build target
85
85
character (:), allocatable :: link_flags
86
-
86
+
87
87
! > Compile flags for this build target
88
88
character (:), allocatable :: compile_flags
89
89
90
90
! > Flag set when first visited to check for circular dependencies
91
91
logical :: touched = .false.
92
-
92
+
93
93
! > Flag set if build target is sorted for building
94
94
logical :: sorted = .false.
95
95
@@ -120,10 +120,10 @@ subroutine targets_from_sources(targets,model,error)
120
120
type (error_t), intent (out ), allocatable :: error
121
121
122
122
call build_target_list(targets,model)
123
-
123
+
124
124
call resolve_module_dependencies(targets,error)
125
125
if (allocated (error)) return
126
-
126
+
127
127
call resolve_target_linking(targets,model)
128
128
129
129
end subroutine targets_from_sources
@@ -176,18 +176,18 @@ subroutine build_target_list(targets,model)
176
176
model% package_name,' lib' // model% package_name// ' .a' ))
177
177
178
178
do j= 1 ,size (model% packages)
179
-
179
+
180
180
associate(sources= >model% packages(j)% sources)
181
181
182
182
do i= 1 ,size (sources)
183
-
183
+
184
184
select case (sources(i)% unit_type)
185
185
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
186
186
187
187
call add_target(targets,source = sources(i), &
188
188
type = FPM_TARGET_OBJECT,&
189
189
output_file = get_object_name(sources(i)))
190
-
190
+
191
191
if (with_lib .and. sources(i)% unit_scope == FPM_SCOPE_LIB) then
192
192
! Archive depends on object
193
193
call add_dependency(targets(1 )% ptr, targets(size (targets))% ptr)
@@ -199,7 +199,7 @@ subroutine build_target_list(targets,model)
199
199
output_file = get_object_name(sources(i)), &
200
200
source = sources(i) &
201
201
)
202
-
202
+
203
203
if (sources(i)% unit_scope == FPM_SCOPE_APP) then
204
204
205
205
exe_dir = ' app'
@@ -226,7 +226,7 @@ subroutine build_target_list(targets,model)
226
226
! Executable depends on library
227
227
call add_dependency(targets(size (targets))% ptr, targets(1 )% ptr)
228
228
end if
229
-
229
+
230
230
end select
231
231
232
232
end do
@@ -239,15 +239,15 @@ subroutine build_target_list(targets,model)
239
239
240
240
function get_object_name (source ) result(object_file)
241
241
! Generate object target path from source name and model params
242
- !
242
+ !
243
243
!
244
244
type (srcfile_t), intent (in ) :: source
245
245
character (:), allocatable :: object_file
246
-
246
+
247
247
integer :: i
248
248
character (1 ), parameter :: filesep = ' /'
249
249
character (:), allocatable :: dir
250
-
250
+
251
251
object_file = canon_path(source% file_name)
252
252
253
253
! Convert any remaining directory separators to underscores
@@ -258,7 +258,7 @@ function get_object_name(source) result(object_file)
258
258
end do
259
259
260
260
object_file = join_path(model% output_directory,model% package_name,object_file)// ' .o'
261
-
261
+
262
262
end function get_object_name
263
263
264
264
end subroutine build_target_list
@@ -298,7 +298,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
298
298
if (present (source)) new_target% source = source
299
299
if (present (link_libraries)) new_target% link_libraries = link_libraries
300
300
allocate (new_target% dependencies(0 ))
301
-
301
+
302
302
targets = [targets, build_target_ptr(new_target)]
303
303
304
304
end subroutine add_target
@@ -314,22 +314,22 @@ subroutine add_dependency(target, dependency)
314
314
end subroutine add_dependency
315
315
316
316
317
- ! > Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
317
+ ! > Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
318
318
! > based on any modules used by the corresponding source file.
319
319
! >
320
320
! >### Source file scoping
321
- ! >
322
- ! > Source files are assigned a scope of either `FPM_SCOPE_LIB`,
321
+ ! >
322
+ ! > Source files are assigned a scope of either `FPM_SCOPE_LIB`,
323
323
! > `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which
324
324
! > modules may be used by the source file:
325
- ! >
325
+ ! >
326
326
! > - Library sources (`FPM_SCOPE_LIB`) may only use modules
327
327
! > also with library scope. This includes library modules
328
328
! > from dependencies.
329
329
! >
330
330
! > - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use
331
331
! > library modules (including dependencies) as well as any modules
332
- ! > corresponding to source files __in the same directory__ as the
332
+ ! > corresponding to source files __in the same directory__ as the
333
333
! > executable source.
334
334
! >
335
335
! > @warning If a module used by a source file cannot be resolved to
@@ -345,7 +345,7 @@ subroutine resolve_module_dependencies(targets,error)
345
345
integer :: i, j
346
346
347
347
do i= 1 ,size (targets)
348
-
348
+
349
349
if (.not. allocated (targets(i)% ptr% source)) cycle
350
350
351
351
do j= 1 ,size (targets(i)% ptr% source% modules_used)
@@ -354,7 +354,7 @@ subroutine resolve_module_dependencies(targets,error)
354
354
! Dependency satisfied in same file, skip
355
355
cycle
356
356
end if
357
-
357
+
358
358
if (any (targets(i)% ptr% source% unit_scope == &
359
359
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
360
360
dep% ptr = > &
@@ -377,7 +377,7 @@ subroutine resolve_module_dependencies(targets,error)
377
377
378
378
end do
379
379
380
- end do
380
+ end do
381
381
382
382
end subroutine resolve_module_dependencies
383
383
@@ -409,7 +409,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
409
409
exit
410
410
case default
411
411
if (present (include_dir)) then
412
- if (dirname(targets(k)% ptr% source% file_name) == include_dir) then
412
+ if (index ( dirname(targets(k)% ptr% source% file_name), include_dir) > 0 ) then ! source file is within the include_dir or a subdirectory
413
413
target_ptr = > targets(k)% ptr
414
414
exit
415
415
end if
@@ -418,7 +418,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
418
418
end if
419
419
420
420
end do
421
-
421
+
422
422
end do
423
423
424
424
end function find_module_dependency
@@ -502,24 +502,24 @@ recursive subroutine get_link_objects(link_objects,target,is_exe)
502
502
do i= 1 ,size (target % dependencies)
503
503
504
504
associate(dep = > target % dependencies(i)% ptr)
505
-
505
+
506
506
if (.not. allocated (dep% source)) cycle
507
-
507
+
508
508
! Skip library dependencies for executable targets
509
- ! since the library archive will always be linked
509
+ ! since the library archive will always be linked
510
510
if (is_exe.and. (dep% source% unit_scope == FPM_SCOPE_LIB)) cycle
511
-
511
+
512
512
! Skip if dependency object already listed
513
513
if (dep% output_file .in . link_objects) cycle
514
514
515
515
! Add dependency object file to link object list
516
516
temp_str% s = dep% output_file
517
517
link_objects = [link_objects, temp_str]
518
518
519
- ! For executable objects, also need to include non-library
519
+ ! For executable objects, also need to include non-library
520
520
! dependencies from dependencies (recurse)
521
521
if (is_exe) call get_link_objects(link_objects,dep,is_exe= .true. )
522
-
522
+
523
523
end associate
524
524
525
525
end do
0 commit comments