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
@@ -185,18 +185,18 @@ subroutine build_target_list(targets,model)
185
185
model% package_name,' lib' // model% package_name// ' .a' ))
186
186
187
187
do j= 1 ,size (model% packages)
188
-
188
+
189
189
associate(sources= >model% packages(j)% sources)
190
190
191
191
do i= 1 ,size (sources)
192
-
192
+
193
193
select case (sources(i)% unit_type)
194
194
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
195
195
196
196
call add_target(targets,source = sources(i), &
197
197
type = FPM_TARGET_OBJECT,&
198
198
output_file = get_object_name(sources(i)))
199
-
199
+
200
200
if (with_lib .and. sources(i)% unit_scope == FPM_SCOPE_LIB) then
201
201
! Archive depends on object
202
202
call add_dependency(targets(1 )% ptr, targets(size (targets))% ptr)
@@ -208,7 +208,7 @@ subroutine build_target_list(targets,model)
208
208
output_file = get_object_name(sources(i)), &
209
209
source = sources(i) &
210
210
)
211
-
211
+
212
212
if (sources(i)% unit_scope == FPM_SCOPE_APP) then
213
213
214
214
exe_dir = ' app'
@@ -235,7 +235,7 @@ subroutine build_target_list(targets,model)
235
235
! Executable depends on library
236
236
call add_dependency(targets(size (targets))% ptr, targets(1 )% ptr)
237
237
end if
238
-
238
+
239
239
end select
240
240
241
241
end do
@@ -248,15 +248,15 @@ subroutine build_target_list(targets,model)
248
248
249
249
function get_object_name (source ) result(object_file)
250
250
! Generate object target path from source name and model params
251
- !
251
+ !
252
252
!
253
253
type (srcfile_t), intent (in ) :: source
254
254
character (:), allocatable :: object_file
255
-
255
+
256
256
integer :: i
257
257
character (1 ), parameter :: filesep = ' /'
258
258
character (:), allocatable :: dir
259
-
259
+
260
260
object_file = canon_path(source% file_name)
261
261
262
262
! Convert any remaining directory separators to underscores
@@ -267,7 +267,7 @@ function get_object_name(source) result(object_file)
267
267
end do
268
268
269
269
object_file = join_path(model% output_directory,model% package_name,object_file)// ' .o'
270
-
270
+
271
271
end function get_object_name
272
272
273
273
end subroutine build_target_list
@@ -307,7 +307,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
307
307
if (present (source)) new_target% source = source
308
308
if (present (link_libraries)) new_target% link_libraries = link_libraries
309
309
allocate (new_target% dependencies(0 ))
310
-
310
+
311
311
targets = [targets, build_target_ptr(new_target)]
312
312
313
313
end subroutine add_target
@@ -323,23 +323,23 @@ subroutine add_dependency(target, dependency)
323
323
end subroutine add_dependency
324
324
325
325
326
- ! > Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
326
+ ! > Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
327
327
! > based on any modules used by the corresponding source file.
328
328
! >
329
329
! >### Source file scoping
330
- ! >
331
- ! > Source files are assigned a scope of either `FPM_SCOPE_LIB`,
330
+ ! >
331
+ ! > Source files are assigned a scope of either `FPM_SCOPE_LIB`,
332
332
! > `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which
333
333
! > modules may be used by the source file:
334
- ! >
334
+ ! >
335
335
! > - Library sources (`FPM_SCOPE_LIB`) may only use modules
336
336
! > also with library scope. This includes library modules
337
337
! > from dependencies.
338
338
! >
339
339
! > - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use
340
340
! > library modules (including dependencies) as well as any modules
341
- ! > corresponding to source files __in the same directory__ as the
342
- ! > executable source.
341
+ ! > corresponding to source files in the same directory or a
342
+ ! > subdirectory of the executable source file .
343
343
! >
344
344
! > @warning If a module used by a source file cannot be resolved to
345
345
! > a source file in the package of the correct scope, then a __fatal error__
@@ -354,7 +354,7 @@ subroutine resolve_module_dependencies(targets,error)
354
354
integer :: i, j
355
355
356
356
do i= 1 ,size (targets)
357
-
357
+
358
358
if (.not. allocated (targets(i)% ptr% source)) cycle
359
359
360
360
do j= 1 ,size (targets(i)% ptr% source% modules_used)
@@ -363,7 +363,7 @@ subroutine resolve_module_dependencies(targets,error)
363
363
! Dependency satisfied in same file, skip
364
364
cycle
365
365
end if
366
-
366
+
367
367
if (any (targets(i)% ptr% source% unit_scope == &
368
368
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
369
369
dep% ptr = > &
@@ -386,7 +386,7 @@ subroutine resolve_module_dependencies(targets,error)
386
386
387
387
end do
388
388
389
- end do
389
+ end do
390
390
391
391
end subroutine resolve_module_dependencies
392
392
@@ -418,7 +418,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
418
418
exit
419
419
case default
420
420
if (present (include_dir)) then
421
- if (dirname(targets(k)% ptr% source% file_name) == include_dir ) then
421
+ if (index ( dirname(targets(k)% ptr% source% file_name), include_dir) == 1 ) then ! source file is within the include_dir or a subdirectory
422
422
target_ptr = > targets(k)% ptr
423
423
exit
424
424
end if
@@ -427,7 +427,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
427
427
end if
428
428
429
429
end do
430
-
430
+
431
431
end do
432
432
433
433
end function find_module_dependency
@@ -523,24 +523,24 @@ recursive subroutine get_link_objects(link_objects,target,is_exe)
523
523
do i= 1 ,size (target % dependencies)
524
524
525
525
associate(dep = > target % dependencies(i)% ptr)
526
-
526
+
527
527
if (.not. allocated (dep% source)) cycle
528
-
528
+
529
529
! Skip library dependencies for executable targets
530
- ! since the library archive will always be linked
530
+ ! since the library archive will always be linked
531
531
if (is_exe.and. (dep% source% unit_scope == FPM_SCOPE_LIB)) cycle
532
-
532
+
533
533
! Skip if dependency object already listed
534
534
if (dep% output_file .in . link_objects) cycle
535
535
536
536
! Add dependency object file to link object list
537
537
temp_str% s = dep% output_file
538
538
link_objects = [link_objects, temp_str]
539
539
540
- ! For executable objects, also need to include non-library
540
+ ! For executable objects, also need to include non-library
541
541
! dependencies from dependencies (recurse)
542
542
if (is_exe) call get_link_objects(link_objects,dep,is_exe= .true. )
543
-
543
+
544
544
end associate
545
545
546
546
end do
0 commit comments