Skip to content

Commit 83d0c4a

Browse files
committed
Add verbose output to git_archive
1 parent c020044 commit 83d0c4a

File tree

2 files changed

+25
-6
lines changed

2 files changed

+25
-6
lines changed

src/fpm/cmd/publish.f90

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ subroutine cmd_publish(settings)
6565
end do
6666

6767
tmp_file = get_temp_filename()
68-
call git_archive('.', tmp_file, error)
68+
call git_archive('.', tmp_file, 'HEAD', settings%verbose, error)
6969
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Archive error: '//error%message)
7070

7171
upload_data = [ &
@@ -91,7 +91,6 @@ subroutine cmd_publish(settings)
9191
end if
9292

9393
if (settings%verbose) then
94-
print *, ''
9594
call print_upload_data(upload_data)
9695
print *, ''
9796
end if

src/fpm/git.f90

Lines changed: 24 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -308,31 +308,51 @@ subroutine info(self, unit, verbosity)
308308
end subroutine info
309309

310310
!> Archive a folder using `git archive`.
311-
subroutine git_archive(source, destination, error)
311+
subroutine git_archive(source, destination, ref, verbose, error)
312312
!> Directory to archive.
313313
character(*), intent(in) :: source
314314
!> Destination of the archive.
315315
character(*), intent(in) :: destination
316+
!> (Symbolic) Reference to be archived.
317+
character(*), intent(in) :: ref
318+
!> Whether to print verbose output.
319+
logical, intent(in) :: verbose
316320
!> Error handling.
317321
type(error_t), allocatable, intent(out) :: error
318322

319323
integer :: stat
320-
character(len=:), allocatable :: cmd_output, archive_format
324+
character(len=:), allocatable :: cmd_output, archive_format, cmd
325+
326+
if (verbose) then
327+
print *, ''
328+
print *, 'Show git archive options:'
329+
print *, ' + git archive -l'
330+
end if
321331

322332
call execute_and_read_output('git archive -l', cmd_output, error)
323333
if (allocated(error)) return
324334

335+
if (verbose) print *, ' ', cmd_output
336+
325337
if (index(cmd_output, 'tar.gz') /= 0) then
326338
archive_format = 'tar.gz'
327339
else
328340
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
329341
end if
330342

331-
call execute_command_line('git archive HEAD --format='//archive_format//' -o '//destination, exitstat=stat)
343+
cmd = 'git archive '//ref//' --format='//archive_format//' -o '//destination
344+
345+
if (verbose) then
346+
print *, ''
347+
print *, 'Archive ', ref, ' using ', archive_format, ':'
348+
print *, ' + ', cmd
349+
print *, ''
350+
end if
351+
352+
call execute_command_line(cmd, exitstat=stat)
332353
if (stat /= 0) then
333354
call fatal_error(error, "Error packing '"//source//"'."); return
334355
end if
335356
end
336357

337-
338358
end module fpm_git

0 commit comments

Comments
 (0)