Skip to content

Commit 0ac5f5b

Browse files
feat(ar): use lib instead of ar on Windows
if ar isn't available
1 parent 0d3611a commit 0ac5f5b

File tree

3 files changed

+48
-28
lines changed

3 files changed

+48
-28
lines changed

src/fpm.f90

Lines changed: 25 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module fpm
44
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
55
fpm_run_settings, fpm_install_settings, fpm_test_settings
66
use fpm_dependency, only : new_dependency_tree
7-
use fpm_environment, only: run
7+
use fpm_environment, only: get_os_type, run, OS_UNKNOWN, OS_WINDOWS
88
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
99
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
1010
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
@@ -62,6 +62,23 @@ subroutine build_model(model, settings, package, error)
6262
model%fortran_compiler = settings%compiler
6363
endif
6464

65+
associate(os_type => get_os_type())
66+
if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
67+
model%archiver = "ar -rs "
68+
else
69+
block
70+
integer :: estat
71+
72+
call execute_command_line("ar --version", exitstat=estat)
73+
if (estat /= 0) then
74+
model%archiver = "lib /OUT:"
75+
else
76+
model%archiver = "ar -rs "
77+
end if
78+
end block
79+
end if
80+
end associate
81+
6582
if (is_unknown_compiler(model%fortran_compiler)) then
6683
write(*, '(*(a:,1x))') &
6784
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -147,7 +164,7 @@ subroutine build_model(model, settings, package, error)
147164
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
148165

149166
if (allocated(dependency%library)) then
150-
167+
151168
if (allocated(dependency%library%source_dir)) then
152169
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
153170
if (is_dir(lib_dir)) then
@@ -165,7 +182,7 @@ subroutine build_model(model, settings, package, error)
165182
end if
166183
end do
167184
end if
168-
185+
169186
end if
170187

171188
if (allocated(dependency%build%link)) then
@@ -178,8 +195,8 @@ subroutine build_model(model, settings, package, error)
178195
if (settings%verbose) then
179196
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
180197
write(*,*)'<INFO> COMPILER: ',settings%compiler
181-
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
182-
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
198+
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
199+
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
183200
end if
184201

185202
! Check for duplicate modules
@@ -190,7 +207,7 @@ subroutine build_model(model, settings, package, error)
190207
end subroutine build_model
191208

192209
! Check for duplicate modules
193-
subroutine check_modules_for_duplicates(model, duplicates_found)
210+
subroutine check_modules_for_duplicates(model, duplicates_found)
194211
type(fpm_model_t), intent(in) :: model
195212
integer :: maxsize
196213
integer :: i,j,k,l,m,modi
@@ -370,7 +387,7 @@ subroutine cmd_run(settings,test)
370387

371388
! Check all names are valid
372389
! or no name and found more than one file
373-
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
390+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
374391
if ( any(.not.found) &
375392
& .or. &
376393
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -420,7 +437,7 @@ subroutine cmd_run(settings,test)
420437
end if
421438
end do
422439
endif
423-
contains
440+
contains
424441
subroutine compact_list_all()
425442
integer, parameter :: LINE_WIDTH = 80
426443
integer :: i, j, nCol

src/fpm_backend.f90

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,28 +1,28 @@
11
!># Build backend
2-
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
2+
!> Uses a list of `[[build_target_ptr]]` and a valid `[[fpm_model]]` instance
33
!> to schedule and execute the compilation and linking of package targets.
4-
!>
4+
!>
55
!> The package build process (`[[build_package]]`) comprises three steps:
66
!>
77
!> 1. __Target sorting:__ topological sort of the target dependency graph (`[[sort_target]]`)
88
!> 2. __Target scheduling:__ group targets into schedule regions based on the sorting (`[[schedule_targets]]`)
99
!> 3. __Target building:__ generate targets by compilation or linking
10-
!>
10+
!>
1111
!> @note If compiled with OpenMP, targets will be build in parallel where possible.
1212
!>
1313
!>### Incremental compilation
14-
!> The backend process supports *incremental* compilation whereby targets are not
14+
!> The backend process supports *incremental* compilation whereby targets are not
1515
!> re-compiled if their corresponding dependencies have not been modified.
16-
!>
16+
!>
1717
!> - Source-based targets (*i.e.* objects) are not re-compiled if the corresponding source
1818
!> file is unmodified AND all of the target dependencies are not marked for re-compilation
1919
!>
20-
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
20+
!> - Link targets (*i.e.* executables and libraries) are not re-compiled if the
2121
!> target output file already exists AND all of the target dependencies are not marked for
2222
!> re-compilation
2323
!>
2424
!> Source file modification is determined by a file digest (hash) which is calculated during
25-
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
25+
!> the source parsing phase ([[fpm_source_parsing]]) and cached to disk after a target is
2626
!> successfully generated.
2727
!>
2828
module fpm_backend
@@ -32,7 +32,7 @@ module fpm_backend
3232
use fpm_model, only: fpm_model_t
3333
use fpm_targets, only: build_target_t, build_target_ptr, &
3434
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35-
35+
3636
use fpm_strings, only: string_cat
3737

3838
implicit none
@@ -58,9 +58,9 @@ subroutine build_package(targets,model)
5858

5959
! Perform depth-first topological sort of targets
6060
do i=1,size(targets)
61-
61+
6262
call sort_target(targets(i)%ptr)
63-
63+
6464
end do
6565

6666
! Construct build schedule queue
@@ -78,20 +78,20 @@ subroutine build_package(targets,model)
7878
end do
7979

8080
end do
81-
81+
8282
end subroutine build_package
8383

8484

85-
!> Topologically sort a target for scheduling by
85+
!> Topologically sort a target for scheduling by
8686
!> recursing over its dependencies.
87-
!>
87+
!>
8888
!> Checks disk-cached source hashes to determine if objects are
8989
!> up-to-date. Up-to-date sources are tagged as skipped.
9090
!>
91-
!> On completion, `target` should either be marked as
91+
!> On completion, `target` should either be marked as
9292
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
9393
!>
94-
!> If `target` is marked as sorted, `target%schedule` should be an
94+
!> If `target` is marked as sorted, `target%schedule` should be an
9595
!> integer greater than zero indicating the region for scheduling
9696
!>
9797
recursive subroutine sort_target(target)
@@ -162,7 +162,7 @@ recursive subroutine sort_target(target)
162162
end if
163163

164164
end do
165-
165+
166166
! Mark flag as processed: either sorted or skipped
167167
target%sorted = .not.target%skip
168168

@@ -242,12 +242,12 @@ subroutine build_target(model,target)
242242
// " -o " // target%output_file)
243243

244244
case (FPM_TARGET_EXECUTABLE)
245-
245+
246246
call run(model%fortran_compiler// " " // target%compile_flags &
247247
//" "//target%link_flags// " -o " // target%output_file)
248248

249249
case (FPM_TARGET_ARCHIVE)
250-
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
250+
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
251251

252252
end select
253253

src/fpm_model.f90

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
!># The fpm package model
22
!>
3-
!> Defines the fpm model data types which encapsulate all information
3+
!> Defines the fpm model data types which encapsulate all information
44
!> required to correctly build a package and its dependencies.
55
!>
66
!> The process (see `[[build_model(subroutine)]]`) for generating a valid `[[fpm_model]]` involves
@@ -117,6 +117,9 @@ module fpm_model
117117
!> Command line name to invoke fortran compiler
118118
character(:), allocatable :: fortran_compiler
119119

120+
!> Command line to invoke for creating static library
121+
character(:), allocatable :: archiver
122+
120123
!> Command line flags passed to fortran for compilation
121124
character(:), allocatable :: fortran_compile_flags
122125

@@ -128,7 +131,7 @@ module fpm_model
128131

129132
!> Native libraries to link against
130133
type(string_t), allocatable :: link_libraries(:)
131-
134+
132135
!> Project dependencies
133136
type(dependency_tree_t) :: deps
134137

0 commit comments

Comments
 (0)