Skip to content

Commit a9adf2b

Browse files
Merge pull request #442 from everythingfunctional/different-archiver-on-windows
Use lib instead of ar on Windows
2 parents fbbfb2c + a1dbbda commit a9adf2b

File tree

4 files changed

+55
-31
lines changed

4 files changed

+55
-31
lines changed

src/fpm.f90

Lines changed: 9 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, get_env
7+
use fpm_environment, only: run, get_env, get_archiver
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, &
@@ -63,6 +63,7 @@ subroutine build_model(model, settings, package, error)
6363
model%fortran_compiler = settings%compiler
6464
endif
6565

66+
model%archiver = get_archiver()
6667
call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
6768
model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
6869

@@ -151,7 +152,7 @@ subroutine build_model(model, settings, package, error)
151152
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
152153

153154
if (allocated(dependency%library)) then
154-
155+
155156
if (allocated(dependency%library%source_dir)) then
156157
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
157158
if (is_dir(lib_dir)) then
@@ -169,7 +170,7 @@ subroutine build_model(model, settings, package, error)
169170
end if
170171
end do
171172
end if
172-
173+
173174
end if
174175

175176
if (allocated(dependency%build%link)) then
@@ -187,8 +188,8 @@ subroutine build_model(model, settings, package, error)
187188
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
188189
write(*,*)'<INFO> COMPILER: ',settings%compiler
189190
write(*,*)'<INFO> C COMPILER: ',model%c_compiler
190-
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
191-
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
191+
write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
192+
write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
192193
end if
193194

194195
! Check for duplicate modules
@@ -199,7 +200,7 @@ subroutine build_model(model, settings, package, error)
199200
end subroutine build_model
200201

201202
! Check for duplicate modules
202-
subroutine check_modules_for_duplicates(model, duplicates_found)
203+
subroutine check_modules_for_duplicates(model, duplicates_found)
203204
type(fpm_model_t), intent(in) :: model
204205
integer :: maxsize
205206
integer :: i,j,k,l,m,modi
@@ -379,7 +380,7 @@ subroutine cmd_run(settings,test)
379380

380381
! Check all names are valid
381382
! or no name and found more than one file
382-
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
383+
toomany= size(settings%name).eq.0 .and. size(executables).gt.1
383384
if ( any(.not.found) &
384385
& .or. &
385386
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -429,7 +430,7 @@ subroutine cmd_run(settings,test)
429430
end if
430431
end do
431432
endif
432-
contains
433+
contains
433434
subroutine compact_list_all()
434435
integer, parameter :: LINE_WIDTH = 80
435436
integer :: i, j, nCol

src/fpm_backend.f90

Lines changed: 17 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,6 @@ module fpm_backend
3232
use fpm_model, only: fpm_model_t
3333
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3434
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35-
3635
use fpm_strings, only: string_cat
3736

3837
implicit none
@@ -58,9 +57,9 @@ subroutine build_package(targets,model)
5857

5958
! Perform depth-first topological sort of targets
6059
do i=1,size(targets)
61-
60+
6261
call sort_target(targets(i)%ptr)
63-
62+
6463
end do
6564

6665
! Construct build schedule queue
@@ -78,20 +77,20 @@ subroutine build_package(targets,model)
7877
end do
7978

8079
end do
81-
80+
8281
end subroutine build_package
8382

8483

85-
!> Topologically sort a target for scheduling by
84+
!> Topologically sort a target for scheduling by
8685
!> recursing over its dependencies.
87-
!>
86+
!>
8887
!> Checks disk-cached source hashes to determine if objects are
8988
!> up-to-date. Up-to-date sources are tagged as skipped.
9089
!>
91-
!> On completion, `target` should either be marked as
90+
!> On completion, `target` should either be marked as
9291
!> sorted (`target%sorted=.true.`) or skipped (`target%skip=.true.`)
9392
!>
94-
!> If `target` is marked as sorted, `target%schedule` should be an
93+
!> If `target` is marked as sorted, `target%schedule` should be an
9594
!> integer greater than zero indicating the region for scheduling
9695
!>
9796
recursive subroutine sort_target(target)
@@ -162,7 +161,7 @@ recursive subroutine sort_target(target)
162161
end if
163162

164163
end do
165-
164+
166165
! Mark flag as processed: either sorted or skipped
167166
target%sorted = .not.target%skip
168167

@@ -246,12 +245,12 @@ subroutine build_target(model,target)
246245
// " -o " // target%output_file)
247246

248247
case (FPM_TARGET_EXECUTABLE)
249-
248+
250249
call run(model%fortran_compiler// " " // target%compile_flags &
251250
//" "//target%link_flags// " -o " // target%output_file)
252251

253252
case (FPM_TARGET_ARCHIVE)
254-
call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "))
253+
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
255254

256255
end select
257256

src/fpm_environment.f90

Lines changed: 24 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
!> This module contains procedures that interact with the programming environment.
2-
!!
2+
!!
33
!! * [get_os_type] -- Determine the OS type
44
!! * [get_env] -- return the value of an environment variable
55
module fpm_environment
@@ -9,6 +9,7 @@ module fpm_environment
99
public :: os_is_unix
1010
public :: run
1111
public :: get_env
12+
public :: get_archiver
1213

1314
integer, parameter, public :: OS_UNKNOWN = 0
1415
integer, parameter, public :: OS_LINUX = 1
@@ -110,7 +111,7 @@ integer function get_os_type() result(r)
110111
end if
111112
end function get_os_type
112113

113-
!> Compare the output of [[get_os_type]] or the optional
114+
!> Compare the output of [[get_os_type]] or the optional
114115
!! passed INTEGER value to the value for OS_WINDOWS
115116
!! and return .TRUE. if they match and .FALSE. otherwise
116117
logical function os_is_unix(os) result(unix)
@@ -150,7 +151,7 @@ end subroutine run
150151
function get_env(NAME,DEFAULT) result(VALUE)
151152
implicit none
152153
!> name of environment variable to get the value of
153-
character(len=*),intent(in) :: NAME
154+
character(len=*),intent(in) :: NAME
154155
!> default value to return if the requested value is undefined or blank
155156
character(len=*),intent(in),optional :: DEFAULT
156157
!> the returned value
@@ -182,4 +183,24 @@ function get_env(NAME,DEFAULT) result(VALUE)
182183
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
183184
end function get_env
184185

186+
function get_archiver() result(archiver)
187+
character(:), allocatable :: archiver
188+
189+
associate(os_type => get_os_type())
190+
if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
191+
archiver = "ar -rs "
192+
else
193+
block
194+
integer :: estat
195+
196+
call execute_command_line("ar --version", exitstat=estat)
197+
if (estat /= 0) then
198+
archiver = "lib /OUT:"
199+
else
200+
archiver = "ar -rs "
201+
end if
202+
end block
203+
end if
204+
end associate
205+
end function
185206
end module fpm_environment

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 name to invoke c compiler
121124
character(:), allocatable :: c_compiler
122125

@@ -131,7 +134,7 @@ module fpm_model
131134

132135
!> Native libraries to link against
133136
type(string_t), allocatable :: link_libraries(:)
134-
137+
135138
!> External modules used
136139
type(string_t), allocatable :: external_modules(:)
137140

0 commit comments

Comments
 (0)