Skip to content

Commit 2d9ef15

Browse files
authored
Merge pull request #912 from fortran-lang/not-get-tmp-from-env
Not get `tmp` folder from `env`
2 parents 5a16564 + 9ff4495 commit 2d9ef15

File tree

3 files changed

+14
-52
lines changed

3 files changed

+14
-52
lines changed

src/fpm/cmd/publish.f90

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -8,8 +8,8 @@ module fpm_cmd_publish
88
use fpm_model, only: fpm_model_t
99
use fpm_error, only: error_t, fpm_stop
1010
use fpm_versioning, only: version_t
11-
use fpm_filesystem, only: exists, join_path, get_tmp_directory
12-
use fpm_git, only: git_archive, compressed_package_name
11+
use fpm_filesystem, only: exists, join_path, get_temp_filename
12+
use fpm_git, only: git_archive
1313
use fpm_downloader, only: downloader_t
1414
use fpm_strings, only: string_t
1515
use fpm_settings, only: official_registry_base_url
@@ -31,7 +31,7 @@ subroutine cmd_publish(settings)
3131
type(error_t), allocatable :: error
3232
type(version_t), allocatable :: version
3333
type(string_t), allocatable :: form_data(:)
34-
character(len=:), allocatable :: tmpdir
34+
character(len=:), allocatable :: tmp_file
3535
type(downloader_t) :: downloader
3636
integer :: i
3737

@@ -69,11 +69,10 @@ subroutine cmd_publish(settings)
6969

7070
if (allocated(settings%token)) form_data = [form_data, string_t('upload_token="'//settings%token//'"')]
7171

72-
call get_tmp_directory(tmpdir, error)
73-
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Tmp directory error: '//error%message)
74-
call git_archive('.', tmpdir, error)
72+
tmp_file = get_temp_filename()
73+
call git_archive('.', tmp_file, error)
7574
if (allocated(error)) call fpm_stop(1, '*cmd_publish* Pack error: '//error%message)
76-
form_data = [form_data, string_t('tarball=@"'//join_path(tmpdir, compressed_package_name)//'"')]
75+
form_data = [form_data, string_t('tarball=@"'//tmp_file//'"')]
7776

7877
if (settings%show_form_data) then
7978
do i = 1, size(form_data)

src/fpm/git.f90

Lines changed: 2 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -5,10 +5,7 @@ module fpm_git
55
implicit none
66

77
public :: git_target_t, git_target_default, git_target_branch, git_target_tag, git_target_revision, git_revision, &
8-
& git_archive, git_matches_manifest, operator(==), compressed_package_name
9-
10-
!> Name of the compressed package that is generated temporarily.
11-
character(len=*), parameter :: compressed_package_name = 'compressed_package'
8+
& git_archive, git_matches_manifest, operator(==)
129

1310
!> Possible git target
1411
type :: enum_descriptor
@@ -326,8 +323,7 @@ subroutine git_archive(source, destination, error)
326323
call fatal_error(error, "Cannot find a suitable archive format for 'git archive'."); return
327324
end if
328325

329-
call execute_command_line('git archive HEAD --format='//archive_format//' -o '// &
330-
& join_path(destination, compressed_package_name), exitstat=stat)
326+
call execute_command_line('git archive HEAD --format='//archive_format//' -o '// destination, exitstat=stat)
331327
if (stat /= 0) then
332328
call fatal_error(error, "Error packing '"//source//"'."); return
333329
end if

src/fpm_filesystem.F90

Lines changed: 6 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,7 @@ module fpm_filesystem
1414
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, list_files, get_local_prefix, &
1515
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, fileopen, fileclose, &
1616
filewrite, warnwrite, parent_dir, is_hidden_file, read_lines, read_lines_expanded, which, run, &
17-
LINE_BUFFER_LEN, os_delete_dir, is_absolute_path, env_variable, get_home, get_tmp_directory, &
18-
execute_and_read_output
17+
LINE_BUFFER_LEN, os_delete_dir, is_absolute_path, env_variable, get_home, execute_and_read_output
1918
integer, parameter :: LINE_BUFFER_LEN = 1000
2019

2120
#ifndef FPM_BOOTSTRAP
@@ -1033,21 +1032,15 @@ subroutine execute_and_read_output(cmd, output, error, exitstat)
10331032
integer, intent(out), optional :: exitstat
10341033

10351034
integer :: cmdstat, unit, stat = 0
1036-
character(len=:), allocatable :: cmdmsg, tmp_path
1035+
character(len=:), allocatable :: cmdmsg, tmp_file
10371036
character(len=1000) :: output_line
10381037

1039-
call get_tmp_directory(tmp_path, error)
1040-
if (allocated(error)) return
1038+
tmp_file = get_temp_filename()
10411039

1042-
if (.not. exists(tmp_path)) call mkdir(tmp_path)
1043-
tmp_path = join_path(tmp_path, 'command_line_output')
1044-
call delete_file(tmp_path)
1045-
call filewrite(tmp_path, [''])
1040+
call execute_command_line(cmd//' > '//tmp_file, exitstat=exitstat, cmdstat=cmdstat)
1041+
if (cmdstat /= 0) call fatal_error(error, '*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
10461042

1047-
call execute_command_line(cmd//' > '//tmp_path, exitstat=exitstat, cmdstat=cmdstat)
1048-
if (cmdstat /= 0) call fpm_stop(1,'*run*: '//"Command failed: '"//cmd//"'. Message: '"//trim(cmdmsg)//"'.")
1049-
1050-
open(unit, file=tmp_path, action='read', status='old')
1043+
open(newunit=unit, file=tmp_file, action='read', status='old')
10511044
output = ''
10521045
do
10531046
read(unit, *, iostat=stat) output_line
@@ -1056,30 +1049,4 @@ subroutine execute_and_read_output(cmd, output, error, exitstat)
10561049
end do
10571050
close(unit, status='delete')
10581051
end
1059-
1060-
!> Get system-dependent tmp directory.
1061-
subroutine get_tmp_directory(tmp_dir, error)
1062-
!> System-dependant tmp directory.
1063-
character(len=:), allocatable, intent(out) :: tmp_dir
1064-
!> Error to handle.
1065-
type(error_t), allocatable, intent(out) :: error
1066-
1067-
tmp_dir = get_env('TMPDIR', '')
1068-
if (tmp_dir /= '') then
1069-
tmp_dir = tmp_dir//'fpm'; return
1070-
end if
1071-
1072-
tmp_dir = get_env('TMP', '')
1073-
if (tmp_dir /= '') then
1074-
tmp_dir = tmp_dir//'fpm'; return
1075-
end if
1076-
1077-
tmp_dir = get_env('TEMP', '')
1078-
if (tmp_dir /= '') then
1079-
tmp_dir = tmp_dir//'fpm'; return
1080-
end if
1081-
1082-
call fatal_error(error, "Couldn't determine system temporary directory.")
1083-
end
1084-
10851052
end module fpm_filesystem

0 commit comments

Comments
 (0)