aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-02-20 12:29:05 +0000
committerLKedward <laurence.kedward@bristol.ac.uk>2021-02-20 12:36:21 +0000
commitd82ce30822019c65723acb537e0d459519ecac57 (patch)
treee4cffeedb97d82df9b52e413b7973402f39eb998
parent0f9bd439e1e1c8621fb982cc95b05473fd7fdff1 (diff)
downloadfpm-d82ce30822019c65723acb537e0d459519ecac57.tar.gz
fpm-d82ce30822019c65723acb537e0d459519ecac57.zip
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.
-rw-r--r--fpm/src/fpm.f908
-rw-r--r--fpm/src/fpm_backend.f9020
-rw-r--r--fpm/src/fpm_model.f9010
-rw-r--r--fpm/src/fpm_targets.f9091
4 files changed, 67 insertions, 62 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 2eedc0f..5837189 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -50,11 +50,7 @@ subroutine build_model(model, settings, package, error)
model%package_name = package%name
- if (allocated(package%build%link)) then
- model%link_libraries = package%build%link
- else
- allocate(model%link_libraries(0))
- end if
+ allocate(model%link_libraries(0))
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
call model%deps%add(package, error)
@@ -70,8 +66,6 @@ subroutine build_model(model, settings, package, error)
call add_compile_flag_defaults(settings%build_name, basename(model%fortran_compiler), model)
- model%link_flags = ''
-
allocate(model%packages(model%deps%ndep))
! Add sources from executable directories
diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90
index f621c64..d60f48e 100644
--- a/fpm/src/fpm_backend.f90
+++ b/fpm/src/fpm_backend.f90
@@ -238,27 +238,13 @@ subroutine build_target(model,target)
select case(target%target_type)
case (FPM_TARGET_OBJECT)
- call run(model%fortran_compiler//" -c " // target%source%file_name // model%fortran_compile_flags &
+ call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
// " -o " // target%output_file)
case (FPM_TARGET_EXECUTABLE)
-
- link_flags = string_cat(target%link_objects," ")
-
- if (allocated(model%library_file)) then
- link_flags = link_flags//" "//model%library_file//" "//model%link_flags
- else
- link_flags = link_flags//" "//model%link_flags
- end if
-
- if (allocated(target%link_libraries)) then
- if (size(target%link_libraries) > 0) then
- link_flags = link_flags // " -l" // string_cat(target%link_libraries," -l")
- end if
- end if
- call run(model%fortran_compiler// " " // model%fortran_compile_flags &
- //" "//link_flags// " -o " // target%output_file)
+ call run(model%fortran_compiler// " " // target%compile_flags &
+ //" "//target%link_flags// " -o " // target%output_file)
case (FPM_TARGET_ARCHIVE)
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90
index 1a9bd92..1a2caab 100644
--- a/fpm/src/fpm_model.f90
+++ b/fpm/src/fpm_model.f90
@@ -127,12 +127,6 @@ type :: fpm_model_t
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags
- !> Command line flags pass for linking
- character(:), allocatable :: link_flags
-
- !> Output file for library archive
- character(:), allocatable :: library_file
-
!> Base directory for build
character(:), allocatable :: output_directory
@@ -277,10 +271,6 @@ function info_model(model) result(s)
s = s // ', fortran_compiler="' // model%fortran_compiler // '"'
! character(:), allocatable :: fortran_compile_flags
s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"'
- ! character(:), allocatable :: link_flags
- s = s // ', link_flags="' // model%link_flags // '"'
- ! character(:), allocatable :: library_file
- s = s // ', library_file="' // model%library_file // '"'
! character(:), allocatable :: output_directory
s = s // ', output_directory="' // model%output_directory // '"'
! type(string_t), allocatable :: link_libraries(:)
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90
index 0742de6..1de9e64 100644
--- a/fpm/src/fpm_targets.f90
+++ b/fpm/src/fpm_targets.f90
@@ -15,7 +15,7 @@
!>
!> For more information, please read the documentation for the procedures:
!>
-!> - `[[targets_from_sources]]`
+!> - `[[build_target_list]]`
!> - `[[resolve_module_dependencies]]`
!>
module fpm_targets
@@ -24,7 +24,7 @@ use fpm_error, only: error_t, fatal_error
use fpm_model
use fpm_environment, only: get_os_type, OS_WINDOWS
use fpm_filesystem, only: dirname, join_path, canon_path
-use fpm_strings, only: string_t, operator(.in.)
+use fpm_strings, only: string_t, operator(.in.), string_cat
implicit none
private
@@ -75,7 +75,13 @@ type build_target_t
!> Objects needed to link this target
type(string_t), allocatable :: link_objects(:)
+
+ !> Link flags for this build target
+ character(:), allocatable :: link_flags
+ !> Compile flags for this build target
+ character(:), allocatable :: compile_flags
+
!> Flag set when first visited to check for circular dependencies
logical :: touched = .false.
@@ -96,6 +102,28 @@ end type build_target_t
contains
+!> High-level wrapper to generate build target information
+subroutine targets_from_sources(targets,model,error)
+
+ !> The generated list of build targets
+ type(build_target_ptr), intent(out), allocatable :: targets(:)
+
+ !> The package model from which to construct the target list
+ type(fpm_model_t), intent(inout), target :: model
+
+ !> Error structure
+ type(error_t), intent(out), allocatable :: error
+
+ call build_target_list(targets,model)
+
+ call resolve_module_dependencies(targets,error)
+ if (allocated(error)) return
+
+ call resolve_target_linking(targets,model)
+
+end subroutine targets_from_sources
+
+
!> Constructs a list of build targets from a list of source files
!>
!>### Source-target mapping
@@ -115,9 +143,7 @@ contains
!> is a library, then the executable target has an additional dependency on the library
!> archive target.
!>
-!> @note Inter-object dependencies based on modules used and provided are generated separately
-!> in `[[resolve_module_dependencies]]` after all targets have been enumerated.
-subroutine targets_from_sources(targets,model,error)
+subroutine build_target_list(targets,model)
!> The generated list of build targets
type(build_target_ptr), intent(out), allocatable :: targets(:)
@@ -125,9 +151,6 @@ subroutine targets_from_sources(targets,model,error)
!> The package model from which to construct the target list
type(fpm_model_t), intent(inout), target :: model
- !> Error structure
- type(error_t), intent(out), allocatable :: error
-
integer :: i, j
character(:), allocatable :: xsuffix, exe_dir
type(build_target_t), pointer :: dep
@@ -207,21 +230,6 @@ subroutine targets_from_sources(targets,model,error)
end do
- if (allocated(model%link_libraries)) then
- do i = 1, size(model%link_libraries)
- model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s
- end do
- end if
-
- if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
- model%library_file = targets(1)%ptr%output_file
- end if
-
- call resolve_module_dependencies(targets,error)
- if (allocated(error)) return
-
- call resolve_target_linking(targets)
-
contains
function get_object_name(source) result(object_file)
@@ -248,7 +256,7 @@ subroutine targets_from_sources(targets,model,error)
end function get_object_name
-end subroutine targets_from_sources
+end subroutine build_target_list
!> 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
end function find_module_dependency
-!> For libraries and executables, build a list of objects required for linking
+!> Construct the linker flags string for each target
+!> `target%link_flags` includes non-library objects and library flags
!>
-!> stored in `target%link_objects`
-!>
-subroutine resolve_target_linking(targets)
+subroutine resolve_target_linking(targets, model)
type(build_target_ptr), intent(inout), target :: targets(:)
+ type(fpm_model_t), intent(in) :: model
integer :: i
+ character(:), allocatable :: global_link_flags
+
+ if (targets(1)%ptr%target_type == FPM_TARGET_ARCHIVE) then
+ global_link_flags = targets(1)%ptr%output_file
+ else
+ allocate(character(0) :: global_link_flags)
+ end if
+
+ if (allocated(model%link_libraries)) then
+ if (size(model%link_libraries) > 0) then
+ global_link_flags = global_link_flags // " -l" // string_cat(model%link_libraries," -l")
+ end if
+ end if
do i=1,size(targets)
associate(target => targets(i)%ptr)
+ target%compile_flags = model%fortran_compile_flags
+
allocate(target%link_objects(0))
if (target%target_type == FPM_TARGET_ARCHIVE) then
call get_link_objects(target%link_objects,target,is_exe=.false.)
+ allocate(character(0) :: target%link_flags)
+
else if (target%target_type == FPM_TARGET_EXECUTABLE) then
call get_link_objects(target%link_objects,target,is_exe=.true.)
+ target%link_flags = string_cat(target%link_objects," ")
+
+ if (allocated(target%link_libraries)) then
+ if (size(target%link_libraries) > 0) then
+ target%link_flags = target%link_flags // " -l" // string_cat(target%link_libraries," -l")
+ end if
+ end if
+
+ target%link_flags = target%link_flags//" "//global_link_flags
+
end if
end associate