aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_backend.f90
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:37:40 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:37:40 +0100
commit7e9c3390b04a0fc746812abd65a574a9dd219c81 (patch)
tree66a5df663bf46aa1df7c8cf174f10902ac06f1e1 /src/fpm_backend.f90
parent086ae55dfa09c1924d2b54bc88ddb1827f9dcfa7 (diff)
parent845217f13a23de91021ba393ef432d68683af282 (diff)
downloadfpm-7e9c3390b04a0fc746812abd65a574a9dd219c81.tar.gz
fpm-7e9c3390b04a0fc746812abd65a574a9dd219c81.zip
Merge branch 'upstream_master' into backend-grace
Diffstat (limited to 'src/fpm_backend.f90')
-rw-r--r--src/fpm_backend.f9076
1 files changed, 52 insertions, 24 deletions
diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90
index 799b7a6..bdec3af 100644
--- a/src/fpm_backend.f90
+++ b/src/fpm_backend.f90
@@ -1,39 +1,38 @@
!># Build backend
-!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
+!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
!> to schedule and execute the compilation and linking of package targets.
-!>
+!>
!> The package build process (`[[build_package]]`) comprises three steps:
!>
!> 1. __Target sorting:__ topological sort of the target dependency graph (`[[sort_target]]`)
!> 2. __Target scheduling:__ group targets into schedule regions based on the sorting (`[[schedule_targets]]`)
!> 3. __Target building:__ generate targets by compilation or linking
-!>
+!>
!> @note If compiled with OpenMP, targets will be build in parallel where possible.
!>
!>### Incremental compilation
-!> The backend process supports *incremental* compilation whereby targets are not
+!> The backend process supports *incremental* compilation whereby targets are not
!> re-compiled if their corresponding dependencies have not been modified.
-!>
+!>
!> - Source-based targets (*i.e.* objects) are not re-compiled if the corresponding source
!> file is unmodified AND all of the target dependencies are not marked for re-compilation
!>
-!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
+!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
!> target output file already exists AND all of the target dependencies are not marked for
!> re-compilation
!>
!> Source file modification is determined by a file digest (hash) which is calculated during
-!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
+!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
!> successfully generated.
!>
module fpm_backend
-use fpm_environment, only: run
-use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
+use fpm_environment, only: run, get_os_type, OS_WINDOWS
+use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, unix_path
use fpm_model, only: fpm_model_t
-use fpm_targets, only: build_target_t, build_target_ptr, &
- FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
-
-use fpm_strings, only: string_cat
+use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
+ FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
+use fpm_strings, only: string_cat, string_t
implicit none
@@ -59,9 +58,9 @@ subroutine build_package(targets,model)
! Perform depth-first topological sort of targets
do i=1,size(targets)
-
+
call sort_target(targets(i)%ptr)
-
+
end do
! Construct build schedule queue
@@ -106,20 +105,20 @@ subroutine build_package(targets,model)
end if
end do
-
+
end subroutine build_package
-!> Topologically sort a target for scheduling by
+!> Topologically sort a target for scheduling by
!> recursing over its dependencies.
-!>
+!>
!> Checks disk-cached source hashes to determine if objects are
!> up-to-date. Up-to-date sources are tagged as skipped.
!>
-!> On completion, `target` should either be marked as
+!> On completion, `target` should either be marked as
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
!>
-!> If `target` is marked as sorted, `target%schedule` should be an
+!> If `target` is marked as sorted, `target%schedule` should be an
!> integer greater than zero indicating the region for scheduling
!>
recursive subroutine sort_target(target)
@@ -190,7 +189,7 @@ recursive subroutine sort_target(target)
end if
end do
-
+
! Mark flag as processed: either sorted or skipped
target%sorted = .not.target%skip
@@ -270,14 +269,28 @@ subroutine build_target(model,target,stat)
call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags &
// " -o " // target%output_file, echo=.true., exitstat=stat)
+ case (FPM_TARGET_C_OBJECT)
+ call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags &
+ // " -o " // target%output_file)
+
case (FPM_TARGET_EXECUTABLE)
-
+
call run(model%fortran_compiler// " " // target%compile_flags &
//" "//target%link_flags// " -o " // target%output_file, echo=.true., exitstat=stat)
case (FPM_TARGET_ARCHIVE)
- call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "), &
- echo=.true., exitstat=stat)
+
+ select case (get_os_type())
+ case (OS_WINDOWS)
+ call write_response_file(target%output_file//".resp" ,target%link_objects)
+ call run(model%archiver // target%output_file // " @" // target%output_file//".resp", &
+ echo=.true., exitstat=stat)
+
+ case default
+ call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "), &
+ echo=.true., exitstat=stat)
+
+ end select
end select
@@ -289,4 +302,19 @@ subroutine build_target(model,target,stat)
end subroutine build_target
+!> Response files allow to read command line options from files.
+!> Whitespace is used to separate the arguments, we will use newlines
+!> as separator to create readable response files which can be inspected
+!> in case of errors.
+subroutine write_response_file(name, argv)
+ character(len=*), intent(in) :: name
+ type(string_t), intent(in) :: argv(:)
+ integer :: iarg, io
+ open(file=name, newunit=io)
+ do iarg = 1, size(argv)
+ write(io, '(a)') unix_path(argv(iarg)%s)
+ end do
+ close(io)
+end subroutine write_response_file
+
end module fpm_backend