Skip to content

Commit b988fe8

Browse files
Merge pull request #409 from everythingfunctional/allow-programs-access-to-subdirectories
Give Programs Access to Code in Subdirectories
2 parents 0560c74 + f77e072 commit b988fe8

File tree

2 files changed

+93
-67
lines changed

2 files changed

+93
-67
lines changed

fpm/src/fpm_targets.f90

Lines changed: 33 additions & 33 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
@@ -185,18 +185,18 @@ subroutine build_target_list(targets,model)
185185
model%package_name,'lib'//model%package_name//'.a'))
186186

187187
do j=1,size(model%packages)
188-
188+
189189
associate(sources=>model%packages(j)%sources)
190190

191191
do i=1,size(sources)
192-
192+
193193
select case (sources(i)%unit_type)
194194
case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE)
195195

196196
call add_target(targets,source = sources(i), &
197197
type = FPM_TARGET_OBJECT,&
198198
output_file = get_object_name(sources(i)))
199-
199+
200200
if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then
201201
! Archive depends on object
202202
call add_dependency(targets(1)%ptr, targets(size(targets))%ptr)
@@ -208,7 +208,7 @@ subroutine build_target_list(targets,model)
208208
output_file = get_object_name(sources(i)), &
209209
source = sources(i) &
210210
)
211-
211+
212212
if (sources(i)%unit_scope == FPM_SCOPE_APP) then
213213

214214
exe_dir = 'app'
@@ -235,7 +235,7 @@ subroutine build_target_list(targets,model)
235235
! Executable depends on library
236236
call add_dependency(targets(size(targets))%ptr, targets(1)%ptr)
237237
end if
238-
238+
239239
end select
240240

241241
end do
@@ -248,15 +248,15 @@ subroutine build_target_list(targets,model)
248248

249249
function get_object_name(source) result(object_file)
250250
! Generate object target path from source name and model params
251-
!
251+
!
252252
!
253253
type(srcfile_t), intent(in) :: source
254254
character(:), allocatable :: object_file
255-
255+
256256
integer :: i
257257
character(1), parameter :: filesep = '/'
258258
character(:), allocatable :: dir
259-
259+
260260
object_file = canon_path(source%file_name)
261261

262262
! Convert any remaining directory separators to underscores
@@ -267,7 +267,7 @@ function get_object_name(source) result(object_file)
267267
end do
268268

269269
object_file = join_path(model%output_directory,model%package_name,object_file)//'.o'
270-
270+
271271
end function get_object_name
272272

273273
end subroutine build_target_list
@@ -307,7 +307,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries)
307307
if (present(source)) new_target%source = source
308308
if (present(link_libraries)) new_target%link_libraries = link_libraries
309309
allocate(new_target%dependencies(0))
310-
310+
311311
targets = [targets, build_target_ptr(new_target)]
312312

313313
end subroutine add_target
@@ -323,23 +323,23 @@ subroutine add_dependency(target, dependency)
323323
end subroutine add_dependency
324324

325325

326-
!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
326+
!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`)
327327
!> based on any modules used by the corresponding source file.
328328
!>
329329
!>### 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`,
332332
!> `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which
333333
!> modules may be used by the source file:
334-
!>
334+
!>
335335
!> - Library sources (`FPM_SCOPE_LIB`) may only use modules
336336
!> also with library scope. This includes library modules
337337
!> from dependencies.
338338
!>
339339
!> - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use
340340
!> 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.
343343
!>
344344
!> @warning If a module used by a source file cannot be resolved to
345345
!> a source file in the package of the correct scope, then a __fatal error__
@@ -354,7 +354,7 @@ subroutine resolve_module_dependencies(targets,error)
354354
integer :: i, j
355355

356356
do i=1,size(targets)
357-
357+
358358
if (.not.allocated(targets(i)%ptr%source)) cycle
359359

360360
do j=1,size(targets(i)%ptr%source%modules_used)
@@ -363,7 +363,7 @@ subroutine resolve_module_dependencies(targets,error)
363363
! Dependency satisfied in same file, skip
364364
cycle
365365
end if
366-
366+
367367
if (any(targets(i)%ptr%source%unit_scope == &
368368
[FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then
369369
dep%ptr => &
@@ -386,7 +386,7 @@ subroutine resolve_module_dependencies(targets,error)
386386

387387
end do
388388

389-
end do
389+
end do
390390

391391
end subroutine resolve_module_dependencies
392392

@@ -418,7 +418,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
418418
exit
419419
case default
420420
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
422422
target_ptr => targets(k)%ptr
423423
exit
424424
end if
@@ -427,7 +427,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p
427427
end if
428428

429429
end do
430-
430+
431431
end do
432432

433433
end function find_module_dependency
@@ -523,24 +523,24 @@ recursive subroutine get_link_objects(link_objects,target,is_exe)
523523
do i=1,size(target%dependencies)
524524

525525
associate(dep => target%dependencies(i)%ptr)
526-
526+
527527
if (.not.allocated(dep%source)) cycle
528-
528+
529529
! Skip library dependencies for executable targets
530-
! since the library archive will always be linked
530+
! since the library archive will always be linked
531531
if (is_exe.and.(dep%source%unit_scope == FPM_SCOPE_LIB)) cycle
532-
532+
533533
! Skip if dependency object already listed
534534
if (dep%output_file .in. link_objects) cycle
535535

536536
! Add dependency object file to link object list
537537
temp_str%s = dep%output_file
538538
link_objects = [link_objects, temp_str]
539539

540-
! For executable objects, also need to include non-library
540+
! For executable objects, also need to include non-library
541541
! dependencies from dependencies (recurse)
542542
if (is_exe) call get_link_objects(link_objects,dep,is_exe=.true.)
543-
543+
544544
end associate
545545

546546
end do

0 commit comments

Comments
 (0)