Skip to content

Commit f3d2c13

Browse files
committed
Use run
1 parent c983e48 commit f3d2c13

File tree

3 files changed

+24
-34
lines changed

3 files changed

+24
-34
lines changed

src/fpm/downloader.f90

Lines changed: 5 additions & 7 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
@@ -81,25 +81,23 @@ subroutine upload_form(endpoint, form_data, verbose, error)
8181
character(len=*), intent(in) :: endpoint
8282
!> Form data to upload.
8383
type(string_t), intent(in) :: form_data(:)
84-
!> Print additional information when true.
84+
!> Print additional information if true.
8585
logical, intent(in) :: verbose
8686
!> Error handling.
8787
type(error_t), allocatable, intent(out) :: error
8888

8989
integer :: stat, i
90-
character(len=:), allocatable :: form_data_str, cmd
90+
character(len=:), allocatable :: form_data_str
9191

9292
form_data_str = ''
9393
do i = 1, size(form_data)
9494
form_data_str = form_data_str//"-F '"//form_data(i)%s//"' "
9595
end do
9696

97-
cmd = 'curl -X POST -H "Content-Type: multipart/form-data" '//form_data_str//endpoint
98-
9997
if (which('curl') /= '') then
10098
print *, 'Uploading package ...'
101-
if (verbose) print *, ' + ', cmd
102-
call execute_command_line(cmd, exitstat=stat)
99+
call run('curl -X POST -H "Content-Type: multipart/form-data" '// &
100+
& form_data_str//endpoint, exitstat=stat, verbose=verbose)
103101
else
104102
call fatal_error(error, "'curl' not installed."); return
105103
end if

src/fpm/git.f90

Lines changed: 5 additions & 21 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, &
@@ -321,35 +322,18 @@ subroutine git_archive(source, destination, ref, verbose, error)
321322
type(error_t), allocatable, intent(out) :: error
322323

323324
integer :: stat
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
325+
character(len=:), allocatable :: cmd_output, archive_format
331326

332-
call execute_and_read_output('git archive -l', cmd_output, error)
327+
call execute_and_read_output('git archive -l', cmd_output, error, verbose)
333328
if (allocated(error)) return
334329

335-
if (verbose) print *, ' ', cmd_output
336-
337330
if (index(cmd_output, 'tar.gz') /= 0) then
338331
archive_format = 'tar.gz'
339332
else
340333
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
341334
end if
342335

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)
336+
call run('git archive '//ref//' --format='//archive_format//' -o '//destination, echo=verbose, exitstat=stat)
353337
if (stat /= 0) then
354338
call fatal_error(error, "Error packing '"//source//"'."); return
355339
end if

src/fpm_filesystem.F90

Lines changed: 14 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1083,24 +1083,31 @@ subroutine get_home(home, error)
10831083
end subroutine get_home
10841084

10851085
!> Execute command line and return output as a string.
1086-
subroutine execute_and_read_output(cmd, output, error, exitstat)
1086+
subroutine execute_and_read_output(cmd, output, error, verbose)
10871087
!> Command to execute.
10881088
character(len=*), intent(in) :: cmd
10891089
!> Command line output.
10901090
character(len=:), allocatable, intent(out) :: output
10911091
!> Error to handle.
10921092
type(error_t), allocatable, intent(out) :: error
1093-
!> Can optionally used for error handling.
1094-
integer, intent(out), optional :: exitstat
1093+
!> Print additional information if true.
1094+
logical, intent(in), optional :: verbose
10951095

1096-
integer :: cmdstat, unit, stat = 0
1096+
integer :: exitstat, unit, stat = 0
10971097
character(len=:), allocatable :: cmdmsg, tmp_file
10981098
character(len=1000) :: output_line
1099+
logical :: is_verbose
1100+
1101+
if (present(verbose)) then
1102+
is_verbose = verbose
1103+
else
1104+
is_verbose = .false.
1105+
end if
10991106

11001107
tmp_file = get_temp_filename()
11011108

1102-
call execute_command_line(cmd//' > '//tmp_file, exitstat=exitstat, cmdstat=cmdstat)
1103-
if (cmdstat /= 0) call fatal_error(error, '*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
1109+
call run(cmd//' > '//tmp_file, exitstat=exitstat, echo=is_verbose)
1110+
if (exitstat /= 0) call fatal_error(error, '*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
11041111

11051112
open(newunit=unit, file=tmp_file, action='read', status='old')
11061113
output = ''
@@ -1109,6 +1116,7 @@ subroutine execute_and_read_output(cmd, output, error, exitstat)
11091116
if (stat /= 0) exit
11101117
output = output//trim(output_line)//' '
11111118
end do
1119+
if (is_verbose) print *, output
11121120
close(unit, status='delete')
11131121
end
11141122

0 commit comments

Comments
 (0)