2727! >
2828module fpm_backend
2929
30- use fpm_environment, only: run
31- use fpm_filesystem, only: dirname, join_path, exists, mkdir
30+ use fpm_environment, only: run, get_os_type, OS_WINDOWS
31+ use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path
3232use fpm_model, only: fpm_model_t
3333use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3434 FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35- use fpm_strings, only: string_cat
35+ use fpm_strings, only: string_cat, string_t
3636
3737implicit none
3838
@@ -250,7 +250,16 @@ subroutine build_target(model,target)
250250 // " " // target % link_flags// " -o " // target % output_file)
251251
252252 case (FPM_TARGET_ARCHIVE)
253- call run(model% archiver // target % output_file // " " // string_cat(target % link_objects," " ))
253+
254+ select case (get_os_type())
255+ case (OS_WINDOWS)
256+ call write_response_file(target % output_file// " .resp" ,target % link_objects)
257+ call run(model% archiver // target % output_file // " @" // target % output_file// " .resp" )
258+
259+ case default
260+ call run(model% archiver // target % output_file // " " // string_cat(target % link_objects," " ))
261+
262+ end select
254263
255264 end select
256265
@@ -262,4 +271,19 @@ subroutine build_target(model,target)
262271
263272end subroutine build_target
264273
274+ ! > Response files allow to read command line options from files.
275+ ! > Whitespace is used to separate the arguments, we will use newlines
276+ ! > as separator to create readable response files which can be inspected
277+ ! > in case of errors.
278+ subroutine write_response_file (name , argv )
279+ character (len=* ), intent (in ) :: name
280+ type (string_t), intent (in ) :: argv(:)
281+ integer :: iarg, io
282+ open (file= name, newunit= io)
283+ do iarg = 1 , size (argv)
284+ write (io, ' (a)' ) unix_path(argv(iarg)% s)
285+ end do
286+ close (io)
287+ end subroutine write_response_file
288+
265289end module fpm_backend
0 commit comments