Skip to content

Commit c5222b1

Browse files
authored
Generalize git_archive for untracked files
1 parent 0dc8cb6 commit c5222b1

File tree

1 file changed

+14
-5
lines changed

1 file changed

+14
-5
lines changed

src/fpm/git.f90

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -424,20 +424,22 @@ pure function descriptor_name(descriptor) result(name)
424424
end function descriptor_name
425425

426426
!> Archive a folder using `git archive`.
427-
subroutine git_archive(source, destination, ref, verbose, error)
427+
subroutine git_archive(source, destination, ref, additional_files, verbose, error)
428428
!> Directory to archive.
429429
character(*), intent(in) :: source
430430
!> Destination of the archive.
431431
character(*), intent(in) :: destination
432432
!> (Symbolic) Reference to be archived.
433433
character(*), intent(in) :: ref
434+
!> (Optional) list of additional untracked files to be added to the archive.
435+
character(*), optional, intent(in) :: additional_files(:)
434436
!> Print additional information if true.
435437
logical, intent(in) :: verbose
436438
!> Error handling.
437439
type(error_t), allocatable, intent(out) :: error
438440

439-
integer :: stat
440-
character(len=:), allocatable :: cmd_output, archive_format
441+
integer :: stat,i
442+
character(len=:), allocatable :: cmd_output, archive_format, add_files
441443

442444
call execute_and_read_output('git archive -l', cmd_output, error, verbose)
443445
if (allocated(error)) return
@@ -448,9 +450,16 @@ subroutine git_archive(source, destination, ref, verbose, error)
448450
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
449451
end if
450452

453+
allocate(character(len=0) :: add_files)
454+
if (present(additional_files) then
455+
do i=1,size(additional_files)
456+
add_files = trim(add_files)//' --add-file='//adjustl(additional_files(i))
457+
end do
458+
endif
459+
451460
call run('git archive '//ref//' &
452-
--format='//archive_format//' &
453-
--add-file=fpm_model.json \
461+
--format='//archive_format// &
462+
add_files//' \
454463
-o '//destination, \
455464
echo=verbose, \
456465
exitstat=stat)

0 commit comments

Comments
 (0)