Skip to content

Commit c983e48

Browse files
committed
Add verbose printout to package upload
1 parent 83d0c4a commit c983e48

File tree

3 files changed

+16
-6
lines changed

3 files changed

+16
-6
lines changed

src/fpm/cmd/publish.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ subroutine cmd_publish(settings)
101101
print *, 'Dry run successful. Generated tarball: ', tmp_file; return
102102
end if
103103

104-
call downloader%upload_form(official_registry_base_url//'/packages', upload_data, error)
104+
call downloader%upload_form(official_registry_base_url//'/packages', upload_data, settings%verbose, error)
105105
call delete_file(tmp_file)
106106
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Upload error: '//error%message)
107107
end

src/fpm/downloader.f90

Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -76,23 +76,30 @@ subroutine get_file(url, tmp_pkg_file, error)
7676
end
7777

7878
!> Perform an http post request with form data.
79-
subroutine upload_form(endpoint, form_data, error)
79+
subroutine upload_form(endpoint, form_data, verbose, error)
80+
!> Endpoint to upload to.
8081
character(len=*), intent(in) :: endpoint
82+
!> Form data to upload.
8183
type(string_t), intent(in) :: form_data(:)
84+
!> Print additional information when true.
85+
logical, intent(in) :: verbose
86+
!> Error handling.
8287
type(error_t), allocatable, intent(out) :: error
8388

8489
integer :: stat, i
85-
character(len=:), allocatable :: form_data_str
90+
character(len=:), allocatable :: form_data_str, cmd
8691

8792
form_data_str = ''
8893
do i = 1, size(form_data)
8994
form_data_str = form_data_str//"-F '"//form_data(i)%s//"' "
9095
end do
9196

97+
cmd = 'curl -X POST -H "Content-Type: multipart/form-data" '//form_data_str//endpoint
98+
9299
if (which('curl') /= '') then
93100
print *, 'Uploading package ...'
94-
call execute_command_line('curl -X POST -H "Content-Type: multipart/form-data" ' &
95-
& //form_data_str//endpoint, exitstat=stat)
101+
if (verbose) print *, ' + ', cmd
102+
call execute_command_line(cmd, exitstat=stat)
96103
else
97104
call fatal_error(error, "'curl' not installed."); return
98105
end if
@@ -104,8 +111,11 @@ subroutine upload_form(endpoint, form_data, error)
104111

105112
!> Unpack a tarball to a destination.
106113
subroutine unpack(tmp_pkg_file, destination, error)
114+
!> Path to tarball.
107115
character(*), intent(in) :: tmp_pkg_file
116+
!> Destination to unpack to.
108117
character(*), intent(in) :: destination
118+
!> Error handling.
109119
type(error_t), allocatable, intent(out) :: error
110120

111121
integer :: stat

src/fpm/git.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -315,7 +315,7 @@ subroutine git_archive(source, destination, ref, verbose, error)
315315
character(*), intent(in) :: destination
316316
!> (Symbolic) Reference to be archived.
317317
character(*), intent(in) :: ref
318-
!> Whether to print verbose output.
318+
!> Print additional information when true.
319319
logical, intent(in) :: verbose
320320
!> Error handling.
321321
type(error_t), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)