Skip to content

Commit a6daeb5

Browse files
feat: give programs access to code in subdirectories
1 parent 47c410e commit a6daeb5

File tree

2 files changed

+65
-65
lines changed

2 files changed

+65
-65
lines changed

fpm/src/fpm_targets.f90

Lines changed: 32 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,14 @@
11
!># Build target handling
22
!>
33
!> 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
55
!> resolution of module-dependencies between build targets
66
!> (`[[resolve_module_dependencies]]`), and the enumeration of
77
!> objects required for link targets (`[[resolve_target_linking]]`).
88
!>
99
!> A build target (`[[build_target_t]]`) is a file to be generated
1010
!> by the backend (compilation and linking).
11-
!>
11+
!>
1212
!> @note The current implementation is ignorant to the existence of
1313
!> module files (`.mod`,`.smod`). Dependencies arising from modules
1414
!> are based on the corresponding object files (`.o`) only.
@@ -83,13 +83,13 @@ module fpm_targets
8383

8484
!> Link flags for this build target
8585
character(:), allocatable :: link_flags
86-
86+
8787
!> Compile flags for this build target
8888
character(:), allocatable :: compile_flags
8989

9090
!> Flag set when first visited to check for circular dependencies
9191
logical :: touched = .false.
92-
92+
9393
!> Flag set if build target is sorted for building
9494
logical :: sorted = .false.
9595

@@ -120,10 +120,10 @@ subroutine targets_from_sources(targets,model,error)
120120
type(error_t), intent(out), allocatable :: error
121121

122122
call build_target_list(targets,model)
123-
123+
124124
call resolve_module_dependencies(targets,error)
125125
if (allocated(error)) return
126-
126+
127127
call resolve_target_linking(targets,model)
128128

129129
end subroutine targets_from_sources
@@ -176,18 +176,18 @@ subroutine build_target_list(targets,model)
176176
model%package_name,'lib'//model%package_name//'.a'))
177177

178178
do j=1,size(model%packages)
179-
179+
180180
associate(sources=>model%packages(j)%sources)
181181

182182
do i=1,size(sources)
183-
183+
184184
select case (sources(i)%unit_type)
185185
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
186186

187187
call add_target(targets,source = sources(i), &
188188
type = FPM_TARGET_OBJECT,&
189189
output_file = get_object_name(sources(i)))
190-
190+
191191
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
192192
! Archive depends on object
193193
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
@@ -199,7 +199,7 @@ subroutine build_target_list(targets,model)
199199
output_file = get_object_name(sources(i)), &
200200
source = sources(i) &
201201
)
202-
202+
203203
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
204204

205205
exe_dir = 'app'
@@ -226,7 +226,7 @@ subroutine build_target_list(targets,model)
226226
! Executable depends on library
227227
call add_dependency(targets(size(targets))%ptr, targets(1)%ptr)
228228
end if
229-
229+
230230
end select
231231

232232
end do
@@ -239,15 +239,15 @@ subroutine build_target_list(targets,model)
239239

240240
function get_object_name(source) result(object_file)
241241
! Generate object target path from source name and model params
242-
!
242+
!
243243
!
244244
type(srcfile_t), intent(in) :: source
245245
character(:), allocatable :: object_file
246-
246+
247247
integer :: i
248248
character(1), parameter :: filesep = '/'
249249
character(:), allocatable :: dir
250-
250+
251251
object_file = canon_path(source%file_name)
252252

253253
! Convert any remaining directory separators to underscores
@@ -258,7 +258,7 @@ function get_object_name(source) result(object_file)
258258
end do
259259

260260
object_file = join_path(model%output_directory,model%package_name,object_file)//'.o'
261-
261+
262262
end function get_object_name
263263

264264
end subroutine build_target_list
@@ -298,7 +298,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
298298
if (present(source)) new_target%source = source
299299
if (present(link_libraries)) new_target%link_libraries = link_libraries
300300
allocate(new_target%dependencies(0))
301-
301+
302302
targets = [targets, build_target_ptr(new_target)]
303303

304304
end subroutine add_target
@@ -314,22 +314,22 @@ subroutine add_dependency(target, dependency)
314314
end subroutine add_dependency
315315

316316

317-
!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
317+
!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
318318
!> based on any modules used by the corresponding source file.
319319
!>
320320
!>### 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`,
323323
!> `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which
324324
!> modules may be used by the source file:
325-
!>
325+
!>
326326
!> - Library sources (`FPM_SCOPE_LIB`) may only use modules
327327
!> also with library scope. This includes library modules
328328
!> from dependencies.
329329
!>
330330
!> - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use
331331
!> 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
333333
!> executable source.
334334
!>
335335
!> @warning If a module used by a source file cannot be resolved to
@@ -345,7 +345,7 @@ subroutine resolve_module_dependencies(targets,error)
345345
integer :: i, j
346346

347347
do i=1,size(targets)
348-
348+
349349
if (.not.allocated(targets(i)%ptr%source)) cycle
350350

351351
do j=1,size(targets(i)%ptr%source%modules_used)
@@ -354,7 +354,7 @@ subroutine resolve_module_dependencies(targets,error)
354354
! Dependency satisfied in same file, skip
355355
cycle
356356
end if
357-
357+
358358
if (any(targets(i)%ptr%source%unit_scope == &
359359
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
360360
dep%ptr => &
@@ -377,7 +377,7 @@ subroutine resolve_module_dependencies(targets,error)
377377

378378
end do
379379

380-
end do
380+
end do
381381

382382
end subroutine resolve_module_dependencies
383383

@@ -409,7 +409,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
409409
exit
410410
case default
411411
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
413413
target_ptr => targets(k)%ptr
414414
exit
415415
end if
@@ -418,7 +418,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
418418
end if
419419

420420
end do
421-
421+
422422
end do
423423

424424
end function find_module_dependency
@@ -502,24 +502,24 @@ recursive subroutine get_link_objects(link_objects,target,is_exe)
502502
do i=1,size(target%dependencies)
503503

504504
associate(dep => target%dependencies(i)%ptr)
505-
505+
506506
if (.not.allocated(dep%source)) cycle
507-
507+
508508
! Skip library dependencies for executable targets
509-
! since the library archive will always be linked
509+
! since the library archive will always be linked
510510
if (is_exe.and.(dep%source%unit_scope == FPM_SCOPE_LIB)) cycle
511-
511+
512512
! Skip if dependency object already listed
513513
if (dep%output_file .in. link_objects) cycle
514514

515515
! Add dependency object file to link object list
516516
temp_str%s = dep%output_file
517517
link_objects = [link_objects, temp_str]
518518

519-
! For executable objects, also need to include non-library
519+
! For executable objects, also need to include non-library
520520
! dependencies from dependencies (recurse)
521521
if (is_exe) call get_link_objects(link_objects,dep,is_exe=.true.)
522-
522+
523523
end associate
524524

525525
end do

0 commit comments

Comments
 (0)