Skip to content

Commit 07fce84

Browse files
authored
Merge pull request #1010 from henilp105/main
fix: add fpm_model.json to the package tarball before uploading to the registry
2 parents f65d65b + a9e4e38 commit 07fce84

File tree

2 files changed

+19
-5
lines changed

2 files changed

+19
-5
lines changed

src/fpm/cmd/publish.f90

+1-1
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, 'HEAD', settings%verbose, error)
68+
call git_archive('.', tmp_file, 'HEAD', additional_files=['fpm_model.json'], verbose=settings%verbose, error=error)
6969
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Archive error: '//error%message)
7070
call model%dump('fpm_model.json', error, json=.true.)
7171
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Model dump error: '//error%message)

src/fpm/git.f90

+18-4
Original file line numberDiff line numberDiff line change
@@ -407,20 +407,22 @@ pure function descriptor_name(descriptor) result(name)
407407
end function descriptor_name
408408

409409
!> Archive a folder using `git archive`.
410-
subroutine git_archive(source, destination, ref, verbose, error)
410+
subroutine git_archive(source, destination, ref, additional_files, verbose, error)
411411
!> Directory to archive.
412412
character(*), intent(in) :: source
413413
!> Destination of the archive.
414414
character(*), intent(in) :: destination
415415
!> (Symbolic) Reference to be archived.
416416
character(*), intent(in) :: ref
417+
!> (Optional) list of additional untracked files to be added to the archive.
418+
character(*), optional, intent(in) :: additional_files(:)
417419
!> Print additional information if true.
418420
logical, intent(in) :: verbose
419421
!> Error handling.
420422
type(error_t), allocatable, intent(out) :: error
421423

422-
integer :: stat
423-
character(len=:), allocatable :: cmd_output, archive_format
424+
integer :: stat,i
425+
character(len=:), allocatable :: cmd_output, archive_format, add_files
424426

425427
call execute_and_read_output('git archive -l', cmd_output, error, verbose)
426428
if (allocated(error)) return
@@ -431,7 +433,19 @@ subroutine git_archive(source, destination, ref, verbose, error)
431433
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
432434
end if
433435

434-
call run('git archive '//ref//' --format='//archive_format//' -o '//destination, echo=verbose, exitstat=stat)
436+
allocate(character(len=0) :: add_files)
437+
if (present(additional_files)) then
438+
do i=1,size(additional_files)
439+
add_files = trim(add_files)//' --add-file='//adjustl(additional_files(i))
440+
end do
441+
endif
442+
443+
call run('git archive '//ref//' &
444+
--format='//archive_format// &
445+
add_files//' \
446+
-o '//destination, \
447+
echo=verbose, \
448+
exitstat=stat)
435449
if (stat /= 0) then
436450
call fatal_error(error, "Error packing '"//source//"'."); return
437451
end if

0 commit comments

Comments
 (0)