Skip to content

Commit 16221b1

Browse files
authored
Merge pull request #938 from fortran-lang/add-verbose-outputs
Add verbose printouts options to `git_archive` and `upload_form`
2 parents 5333702 + 9be4b9c commit 16221b1

File tree

4 files changed

+40
-23
lines changed

4 files changed

+40
-23
lines changed

src/fpm/cmd/publish.f90

Lines changed: 2 additions & 3 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
@@ -102,7 +101,7 @@ subroutine cmd_publish(settings)
102101
print *, 'Dry run successful. Generated tarball: ', tmp_file; return
103102
end if
104103

105-
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)
106105
call delete_file(tmp_file)
107106
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Upload error: '//error%message)
108107
end

src/fpm/downloader.f90

Lines changed: 12 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
module fpm_downloader
22
use fpm_error, only: error_t, fatal_error
3-
use fpm_filesystem, only: which
3+
use fpm_filesystem, only: which, run
44
use fpm_versioning, only: version_t
55
use jonquil, only: json_object, json_value, json_error, json_load, cast_to_object
66
use fpm_strings, only: string_t
@@ -76,9 +76,14 @@ 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 if true.
85+
logical, intent(in) :: verbose
86+
!> Error handling.
8287
type(error_t), allocatable, intent(out) :: error
8388

8489
integer :: stat, i
@@ -91,8 +96,8 @@ subroutine upload_form(endpoint, form_data, error)
9196

9297
if (which('curl') /= '') then
9398
print *, 'Uploading package ...'
94-
call execute_command_line('curl -X POST -H "Content-Type: multipart/form-data" ' &
95-
& //form_data_str//endpoint, exitstat=stat)
99+
call run('curl -X POST -H "Content-Type: multipart/form-data" '// &
100+
& form_data_str//endpoint, exitstat=stat, echo=verbose)
96101
else
97102
call fatal_error(error, "'curl' not installed."); return
98103
end if
@@ -104,8 +109,11 @@ subroutine upload_form(endpoint, form_data, error)
104109

105110
!> Unpack a tarball to a destination.
106111
subroutine unpack(tmp_pkg_file, destination, error)
112+
!> Path to tarball.
107113
character(*), intent(in) :: tmp_pkg_file
114+
!> Destination to unpack to.
108115
character(*), intent(in) :: destination
116+
!> Error handling.
109117
type(error_t), allocatable, intent(out) :: error
110118

111119
integer :: stat

src/fpm/git.f90

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
!> Implementation for interacting with git repositories.
22
module fpm_git
33
use fpm_error, only: error_t, fatal_error
4-
use fpm_filesystem, only : get_temp_filename, getline, join_path, execute_and_read_output
4+
use fpm_filesystem, only : get_temp_filename, getline, join_path, execute_and_read_output, run
5+
56
implicit none
67

78
public :: git_target_t, git_target_default, git_target_branch, git_target_tag, git_target_revision, git_revision, &
@@ -308,18 +309,22 @@ subroutine info(self, unit, verbosity)
308309
end subroutine info
309310

310311
!> Archive a folder using `git archive`.
311-
subroutine git_archive(source, destination, error)
312+
subroutine git_archive(source, destination, ref, verbose, error)
312313
!> Directory to archive.
313314
character(*), intent(in) :: source
314315
!> Destination of the archive.
315316
character(*), intent(in) :: destination
317+
!> (Symbolic) Reference to be archived.
318+
character(*), intent(in) :: ref
319+
!> Print additional information if true.
320+
logical, intent(in) :: verbose
316321
!> Error handling.
317322
type(error_t), allocatable, intent(out) :: error
318323

319324
integer :: stat
320325
character(len=:), allocatable :: cmd_output, archive_format
321326

322-
call execute_and_read_output('git archive -l', cmd_output, error)
327+
call execute_and_read_output('git archive -l', cmd_output, error, verbose)
323328
if (allocated(error)) return
324329

325330
if (index(cmd_output, 'tar.gz') /= 0) then
@@ -328,11 +333,10 @@ subroutine git_archive(source, destination, error)
328333
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
329334
end if
330335

331-
call execute_command_line('git archive HEAD --format='//archive_format//' -o '//destination, exitstat=stat)
336+
call run('git archive '//ref//' --format='//archive_format//' -o '//destination, echo=verbose, exitstat=stat)
332337
if (stat /= 0) then
333338
call fatal_error(error, "Error packing '"//source//"'."); return
334339
end if
335340
end
336341

337-
338342
end module fpm_git

src/fpm_filesystem.F90

Lines changed: 17 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -684,7 +684,6 @@ subroutine getline(unit, line, iostat, iomsg)
684684
integer :: size
685685
integer :: stat
686686

687-
688687
allocate(character(len=0) :: line)
689688
do
690689
read(unit, '(a)', advance='no', iostat=stat, iomsg=msg, size=size) &
@@ -1119,24 +1118,30 @@ subroutine get_home(home, error)
11191118
end subroutine get_home
11201119

11211120
!> Execute command line and return output as a string.
1122-
subroutine execute_and_read_output(cmd, output, error, exitstat)
1121+
subroutine execute_and_read_output(cmd, output, error, verbose)
11231122
!> Command to execute.
11241123
character(len=*), intent(in) :: cmd
11251124
!> Command line output.
11261125
character(len=:), allocatable, intent(out) :: output
11271126
!> Error to handle.
11281127
type(error_t), allocatable, intent(out) :: error
1129-
!> Can optionally used for error handling.
1130-
integer, intent(out), optional :: exitstat
1128+
!> Print additional information if true.
1129+
logical, intent(in), optional :: verbose
1130+
1131+
integer :: exitstat, unit, stat
1132+
character(len=:), allocatable :: cmdmsg, tmp_file, output_line
1133+
logical :: is_verbose
11311134

1132-
integer :: cmdstat, unit, stat = 0
1133-
character(len=:), allocatable :: cmdmsg, tmp_file
1134-
character(len=:),allocatable :: output_line
1135+
if (present(verbose)) then
1136+
is_verbose = verbose
1137+
else
1138+
is_verbose = .false.
1139+
end if
11351140

11361141
tmp_file = get_temp_filename()
11371142

1138-
call execute_command_line(cmd//' > '//tmp_file, exitstat=exitstat, cmdstat=cmdstat)
1139-
if (cmdstat /= 0) call fatal_error(error, '*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
1143+
call run(cmd//' > '//tmp_file, exitstat=exitstat, echo=is_verbose)
1144+
if (exitstat /= 0) call fatal_error(error, '*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
11401145

11411146
open(newunit=unit, file=tmp_file, action='read', status='old')
11421147
output = ''
@@ -1145,8 +1150,9 @@ subroutine execute_and_read_output(cmd, output, error, exitstat)
11451150
if (stat /= 0) exit
11461151
output = output//output_line//' '
11471152
end do
1148-
close(unit, status='delete',iostat=stat)
1149-
end subroutine execute_and_read_output
1153+
if (is_verbose) print *, output
1154+
close(unit, status='delete')
1155+
end
11501156

11511157
!> Ensure a windows path is converted to an 8.3 DOS path if it contains spaces
11521158
function get_dos_path(path,error)

0 commit comments

Comments
 (0)