Skip to content

Commit

Permalink
Fix: returns iostat for delete_file, but does not process it.
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha committed Dec 5, 2022
1 parent 9640770 commit 2525343
Show file tree
Hide file tree
Showing 2 changed files with 11 additions and 9 deletions.
13 changes: 6 additions & 7 deletions src/fpm_compiler.f90
Original file line number Diff line number Diff line change
Expand Up @@ -937,9 +937,9 @@ end subroutine link


!> Create an archive
!> @todo An OMP critical section is added for Windows OS,
!> which may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
!> see issue #707 and #708.
!> @todo For Windows OS, the `delete_file` returns `iostat`, but we does not process it.
!> This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
!> see issue #707, #708 and #808.
subroutine make_archive(self, output, args, log_file, stat)
!> Instance of the archiver object
class(archiver_t), intent(in) :: self
Expand All @@ -951,14 +951,13 @@ subroutine make_archive(self, output, args, log_file, stat)
character(len=*), intent(in) :: log_file
!> Status flag
integer, intent(out) :: stat
integer :: istat

if (self%use_response_file) then
!$omp critical
call write_response_file(output//".resp" , args)
call run(self%ar // output // " @" // output//".resp", echo=self%echo, &
& verbose=self%verbose, redirect=log_file, exitstat=stat)
call delete_file(output//".resp")
!$omp end critical
call delete_file(output//".resp", iostat=istat)
else
call run(self%ar // output // " " // string_cat(args, " "), &
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
Expand All @@ -976,7 +975,7 @@ subroutine write_response_file(name, argv)

integer :: iarg, io

open(file=name, newunit=io)
open(file=name, newunit=io, status='replace')
do iarg = 1, size(argv)
write(io, '(a)') unix_path(argv(iarg)%s)
end do
Expand Down
7 changes: 5 additions & 2 deletions src/fpm_filesystem.F90
Original file line number Diff line number Diff line change
Expand Up @@ -681,14 +681,17 @@ end subroutine getline


!> delete a file by filename
subroutine delete_file(file)
subroutine delete_file(file, iostat)
!> file to delete
character(len=*), intent(in) :: file
!> status of operation
integer, intent(out), optional :: iostat
logical :: exist
integer :: unit
inquire(file=file, exist=exist)
if (exist) then
open(file=file, newunit=unit)
close(unit, status="delete")
close(unit, status="delete", iostat=iostat)
end if
end subroutine delete_file

Expand Down

0 comments on commit 2525343

Please sign in to comment.