@@ -4,7 +4,7 @@ module fpm
4
4
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
5
5
fpm_run_settings, fpm_install_settings, fpm_test_settings
6
6
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
8
8
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
9
9
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
10
10
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
@@ -62,6 +62,23 @@ subroutine build_model(model, settings, package, error)
62
62
model% fortran_compiler = settings% compiler
63
63
endif
64
64
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
+
65
82
if (is_unknown_compiler(model% fortran_compiler)) then
66
83
write (* , ' (*(a:,1x))' ) &
67
84
" <WARN>" , " Unknown compiler" , model% fortran_compiler, " requested!" , &
@@ -147,7 +164,7 @@ subroutine build_model(model, settings, package, error)
147
164
if (.not. allocated (model% packages(i)% sources)) allocate (model% packages(i)% sources(0 ))
148
165
149
166
if (allocated (dependency% library)) then
150
-
167
+
151
168
if (allocated (dependency% library% source_dir)) then
152
169
lib_dir = join_path(dep% proj_dir, dependency% library% source_dir)
153
170
if (is_dir(lib_dir)) then
@@ -165,7 +182,7 @@ subroutine build_model(model, settings, package, error)
165
182
end if
166
183
end do
167
184
end if
168
-
185
+
169
186
end if
170
187
171
188
if (allocated (dependency% build% link)) then
@@ -178,8 +195,8 @@ subroutine build_model(model, settings, package, error)
178
195
if (settings% verbose) then
179
196
write (* ,* )' <INFO> BUILD_NAME: ' ,settings% build_name
180
197
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,' ,' ),' ]'
183
200
end if
184
201
185
202
! Check for duplicate modules
@@ -190,7 +207,7 @@ subroutine build_model(model, settings, package, error)
190
207
end subroutine build_model
191
208
192
209
! Check for duplicate modules
193
- subroutine check_modules_for_duplicates (model , duplicates_found )
210
+ subroutine check_modules_for_duplicates (model , duplicates_found )
194
211
type (fpm_model_t), intent (in ) :: model
195
212
integer :: maxsize
196
213
integer :: i,j,k,l,m,modi
@@ -370,7 +387,7 @@ subroutine cmd_run(settings,test)
370
387
371
388
! Check all names are valid
372
389
! 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
374
391
if ( any (.not. found) &
375
392
& .or. &
376
393
& ( (toomany .and. .not. test) .or. (toomany .and. settings% runner .ne. ' ' ) ) &
@@ -420,7 +437,7 @@ subroutine cmd_run(settings,test)
420
437
end if
421
438
end do
422
439
endif
423
- contains
440
+ contains
424
441
subroutine compact_list_all ()
425
442
integer , parameter :: LINE_WIDTH = 80
426
443
integer :: i, j, nCol
0 commit comments