Skip to content

Commit d82ce30

Browse files
committed
Refactor target flag management
Backend simplified to use compiler and linker flags on per target basis. Removes redundant link_flags field in model structure. Fixes benign issue with duplicated link flags.
1 parent 0f9bd43 commit d82ce30

File tree

4 files changed

+67
-62
lines changed

4 files changed

+67
-62
lines changed

fpm/src/fpm.f90

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -50,11 +50,7 @@ subroutine build_model(model, settings, package, error)
5050

5151
model%package_name = package%name
5252

53-
if (allocated(package%build%link)) then
54-
model%link_libraries = package%build%link
55-
else
56-
allocate(model%link_libraries(0))
57-
end if
53+
allocate(model%link_libraries(0))
5854

5955
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
6056
call model%deps%add(package, error)
@@ -70,8 +66,6 @@ subroutine build_model(model, settings, package, error)
7066

7167
call add_compile_flag_defaults(settings%build_name, basename(model%fortran_compiler), model)
7268

73-
model%link_flags = ''
74-
7569
allocate(model%packages(model%deps%ndep))
7670

7771
! Add sources from executable directories

fpm/src/fpm_backend.f90

Lines changed: 3 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -238,27 +238,13 @@ subroutine build_target(model,target)
238238
select case(target%target_type)
239239

240240
case (FPM_TARGET_OBJECT)
241-
call run(model%fortran_compiler//" -c " // target%source%file_name // model%fortran_compile_flags &
241+
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
242242
// " -o " // target%output_file)
243243

244244
case (FPM_TARGET_EXECUTABLE)
245-
246-
link_flags = string_cat(target%link_objects," ")
247-
248-
if (allocated(model%library_file)) then
249-
link_flags = link_flags//" "//model%library_file//" "//model%link_flags
250-
else
251-
link_flags = link_flags//" "//model%link_flags
252-
end if
253-
254-
if (allocated(target%link_libraries)) then
255-
if (size(target%link_libraries) > 0) then
256-
link_flags = link_flags // " -l" // string_cat(target%link_libraries," -l")
257-
end if
258-
end if
259245

260-
call run(model%fortran_compiler// " " // model%fortran_compile_flags &
261-
//" "//link_flags// " -o " // target%output_file)
246+
call run(model%fortran_compiler// " " // target%compile_flags &
247+
//" "//target%link_flags// " -o " // target%output_file)
262248

263249
case (FPM_TARGET_ARCHIVE)
264250
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))

fpm/src/fpm_model.f90

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -127,12 +127,6 @@ module fpm_model
127127
!> Command line flags passed to fortran for compilation
128128
character(:), allocatable :: fortran_compile_flags
129129

130-
!> Command line flags pass for linking
131-
character(:), allocatable :: link_flags
132-
133-
!> Output file for library archive
134-
character(:), allocatable :: library_file
135-
136130
!> Base directory for build
137131
character(:), allocatable :: output_directory
138132

@@ -277,10 +271,6 @@ function info_model(model) result(s)
277271
s = s // ', fortran_compiler="' // model%fortran_compiler // '"'
278272
! character(:), allocatable :: fortran_compile_flags
279273
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
280-
! character(:), allocatable :: link_flags
281-
s = s // ', link_flags="' // model%link_flags // '"'
282-
! character(:), allocatable :: library_file
283-
s = s // ', library_file="' // model%library_file // '"'
284274
! character(:), allocatable :: output_directory
285275
s = s // ', output_directory="' // model%output_directory // '"'
286276
! type(string_t), allocatable :: link_libraries(:)

fpm/src/fpm_targets.f90

Lines changed: 63 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@
1515
!>
1616
!> For more information, please read the documentation for the procedures:
1717
!>
18-
!> - `[[targets_from_sources]]`
18+
!> - `[[build_target_list]]`
1919
!> - `[[resolve_module_dependencies]]`
2020
!>
2121
module fpm_targets
@@ -24,7 +24,7 @@ module fpm_targets
2424
use fpm_model
2525
use fpm_environment, only: get_os_type, OS_WINDOWS
2626
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
2828
implicit none
2929

3030
private
@@ -75,7 +75,13 @@ module fpm_targets
7575

7676
!> Objects needed to link this target
7777
type(string_t), allocatable :: link_objects(:)
78+
79+
!> Link flags for this build target
80+
character(:), allocatable :: link_flags
7881

82+
!> Compile flags for this build target
83+
character(:), allocatable :: compile_flags
84+
7985
!> Flag set when first visited to check for circular dependencies
8086
logical :: touched = .false.
8187

@@ -96,6 +102,28 @@ module fpm_targets
96102

97103
contains
98104

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+
99127
!> Constructs a list of build targets from a list of source files
100128
!>
101129
!>### Source-target mapping
@@ -115,19 +143,14 @@ module fpm_targets
115143
!> is a library, then the executable target has an additional dependency on the library
116144
!> archive target.
117145
!>
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)
121147

122148
!> The generated list of build targets
123149
type(build_target_ptr), intent(out), allocatable :: targets(:)
124150

125151
!> The package model from which to construct the target list
126152
type(fpm_model_t), intent(inout), target :: model
127153

128-
!> Error structure
129-
type(error_t), intent(out), allocatable :: error
130-
131154
integer :: i, j
132155
character(:), allocatable :: xsuffix, exe_dir
133156
type(build_target_t), pointer :: dep
@@ -207,21 +230,6 @@ subroutine targets_from_sources(targets,model,error)
207230

208231
end do
209232

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-
225233
contains
226234

227235
function get_object_name(source) result(object_file)
@@ -248,7 +256,7 @@ function get_object_name(source) result(object_file)
248256

249257
end function get_object_name
250258

251-
end subroutine targets_from_sources
259+
end subroutine build_target_list
252260

253261

254262
!> 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
411419
end function find_module_dependency
412420

413421

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
415424
!>
416-
!> stored in `target%link_objects`
417-
!>
418-
subroutine resolve_target_linking(targets)
425+
subroutine resolve_target_linking(targets, model)
419426
type(build_target_ptr), intent(inout), target :: targets(:)
427+
type(fpm_model_t), intent(in) :: model
420428

421429
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
422443

423444
do i=1,size(targets)
424445

425446
associate(target => targets(i)%ptr)
426447

448+
target%compile_flags = model%fortran_compile_flags
449+
427450
allocate(target%link_objects(0))
428451

429452
if (target%target_type == FPM_TARGET_ARCHIVE) then
430453

431454
call get_link_objects(target%link_objects,target,is_exe=.false.)
432455

456+
allocate(character(0) :: target%link_flags)
457+
433458
else if (target%target_type == FPM_TARGET_EXECUTABLE) then
434459

435460
call get_link_objects(target%link_objects,target,is_exe=.true.)
436461

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+
437472
end if
438473

439474
end associate

0 commit comments

Comments
 (0)