aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBrad Richardson <everythingfunctional@protonmail.com>2021-04-15 14:59:15 -0500
committerBrad Richardson <everythingfunctional@protonmail.com>2021-04-15 14:59:15 -0500
commit0ac5f5bef94c8f12caa64f19fe6cb5026a5535c0 (patch)
tree11a6070e2ca99ab9fd6409a472c8f88c6622a0f1
parent0d3611a5f3e7a2d7cb88ec8637a9d898b2ce4cfb (diff)
downloadfpm-0ac5f5bef94c8f12caa64f19fe6cb5026a5535c0.tar.gz
fpm-0ac5f5bef94c8f12caa64f19fe6cb5026a5535c0.zip
feat(ar): use lib instead of ar on Windows
if ar isn't available
-rw-r--r--src/fpm.f9033
-rw-r--r--src/fpm_backend.f9036
-rw-r--r--src/fpm_model.f907
3 files changed, 48 insertions, 28 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 31b68ff..3e2b518 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -4,7 +4,7 @@ use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_dependency, only : new_dependency_tree
-use fpm_environment, only: run
+use fpm_environment, only: get_os_type, run, OS_UNKNOWN, OS_WINDOWS
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
@@ -62,6 +62,23 @@ subroutine build_model(model, settings, package, error)
model%fortran_compiler = settings%compiler
endif
+ associate(os_type => get_os_type())
+ if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
+ model%archiver = "ar -rs "
+ else
+ block
+ integer :: estat
+
+ call execute_command_line("ar --version", exitstat=estat)
+ if (estat /= 0) then
+ model%archiver = "lib /OUT:"
+ else
+ model%archiver = "ar -rs "
+ end if
+ end block
+ end if
+ end associate
+
if (is_unknown_compiler(model%fortran_compiler)) then
write(*, '(*(a:,1x))') &
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -147,7 +164,7 @@ subroutine build_model(model, settings, package, error)
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
if (allocated(dependency%library)) then
-
+
if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
@@ -165,7 +182,7 @@ subroutine build_model(model, settings, package, error)
end if
end do
end if
-
+
end if
if (allocated(dependency%build%link)) then
@@ -178,8 +195,8 @@ subroutine build_model(model, settings, package, error)
if (settings%verbose) then
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
write(*,*)'<INFO> COMPILER: ',settings%compiler
- write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
- write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
+ write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
+ write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if
! Check for duplicate modules
@@ -190,7 +207,7 @@ subroutine build_model(model, settings, package, error)
end subroutine build_model
! Check for duplicate modules
-subroutine check_modules_for_duplicates(model, duplicates_found)
+subroutine check_modules_for_duplicates(model, duplicates_found)
type(fpm_model_t), intent(in) :: model
integer :: maxsize
integer :: i,j,k,l,m,modi
@@ -370,7 +387,7 @@ subroutine cmd_run(settings,test)
! Check all names are valid
! or no name and found more than one file
- toomany= size(settings%name).eq.0 .and. size(executables).gt.1
+ toomany= size(settings%name).eq.0 .and. size(executables).gt.1
if ( any(.not.found) &
& .or. &
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -420,7 +437,7 @@ subroutine cmd_run(settings,test)
end if
end do
endif
- contains
+ contains
subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol
diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90
index 74cef61..f84d2ea 100644
--- a/src/fpm_backend.f90
+++ b/src/fpm_backend.f90
@@ -1,28 +1,28 @@
!># 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
@@ -32,7 +32,7 @@ use fpm_filesystem, only: dirname, join_path, exists, mkdir
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
implicit none
@@ -58,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
@@ -78,20 +78,20 @@ subroutine build_package(targets,model)
end do
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)
@@ -162,7 +162,7 @@ recursive subroutine sort_target(target)
end if
end do
-
+
! Mark flag as processed: either sorted or skipped
target%sorted = .not.target%skip
@@ -242,12 +242,12 @@ subroutine build_target(model,target)
// " -o " // target%output_file)
case (FPM_TARGET_EXECUTABLE)
-
+
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," "))
+ call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
end select
diff --git a/src/fpm_model.f90 b/src/fpm_model.f90
index bfb0115..84f70d4 100644
--- a/src/fpm_model.f90
+++ b/src/fpm_model.f90
@@ -1,6 +1,6 @@
!># The fpm package model
!>
-!> Defines the fpm model data types which encapsulate all information
+!> Defines the fpm model data types which encapsulate all information
!> required to correctly build a package and its dependencies.
!>
!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` involves
@@ -117,6 +117,9 @@ type :: fpm_model_t
!> Command line name to invoke fortran compiler
character(:), allocatable :: fortran_compiler
+ !> Command line to invoke for creating static library
+ character(:), allocatable :: archiver
+
!> Command line flags passed to fortran for compilation
character(:), allocatable :: fortran_compile_flags
@@ -128,7 +131,7 @@ type :: fpm_model_t
!> Native libraries to link against
type(string_t), allocatable :: link_libraries(:)
-
+
!> Project dependencies
type(dependency_tree_t) :: deps