Skip to content

Commit bac6f60

Browse files
committed
Remove ENV_VARIABLE() as it duplicates the functionality of GET_ENV()
The ENV_VARIABLE() procedure is performing functions already available in the GET_ENV() procedure. This changes the ENV_VARIABLE() calls to GET_ENV() calls to eliminate the duplication functionality.
1 parent c020044 commit bac6f60

File tree

2 files changed

+9
-33
lines changed

2 files changed

+9
-33
lines changed

src/fpm_compiler.F90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@
2828
module fpm_compiler
2929
use,intrinsic :: iso_fortran_env, only: stderr=>error_unit
3030
use fpm_environment, only: &
31-
get_env, &
3231
get_os_type, &
3332
OS_LINUX, &
3433
OS_MACOS, &

src/fpm_filesystem.F90

Lines changed: 9 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +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, execute_and_read_output, &
17+
LINE_BUFFER_LEN, os_delete_dir, is_absolute_path, get_home, execute_and_read_output, &
1818
get_dos_path
1919
integer, parameter :: LINE_BUFFER_LEN = 32768
2020

@@ -54,29 +54,6 @@ end function c_is_dir
5454

5555
contains
5656

57-
58-
!> return value of environment variable
59-
subroutine env_variable(var, name)
60-
character(len=:), allocatable, intent(out) :: var
61-
character(len=*), intent(in) :: name
62-
integer :: length, stat
63-
64-
call get_environment_variable(name, length=length, status=stat)
65-
if (stat /= 0) return
66-
67-
allocate(character(len=length) :: var)
68-
69-
if (length > 0) then
70-
call get_environment_variable(name, var, status=stat)
71-
if (stat /= 0) then
72-
deallocate(var)
73-
return
74-
end if
75-
end if
76-
77-
end subroutine env_variable
78-
79-
8057
!> Extract filename from path with/without suffix
8158
function basename(path,suffix) result (base)
8259

@@ -1017,15 +994,15 @@ function get_local_prefix(os) result(prefix)
1017994
character(len=:), allocatable :: home
1018995

1019996
if (os_is_unix(os)) then
1020-
call env_variable(home, "HOME")
1021-
if (allocated(home)) then
997+
home=get_env('HOME','')
998+
if (home /= '' ) then
1022999
prefix = join_path(home, ".local")
10231000
else
10241001
prefix = default_prefix_unix
10251002
end if
10261003
else
1027-
call env_variable(home, "APPDATA")
1028-
if (allocated(home)) then
1004+
home=get_env('APPDATA','')
1005+
if (home /= '' ) then
10291006
prefix = join_path(home, "local")
10301007
else
10311008
prefix = default_prefix_win
@@ -1068,14 +1045,14 @@ subroutine get_home(home, error)
10681045
type(error_t), allocatable, intent(out) :: error
10691046

10701047
if (os_is_unix()) then
1071-
call env_variable(home, 'HOME')
1072-
if (.not. allocated(home)) then
1048+
home=get_env('HOME','')
1049+
if ( home == '' ) then
10731050
call fatal_error(error, "Couldn't retrieve 'HOME' variable")
10741051
return
10751052
end if
10761053
else
1077-
call env_variable(home, 'USERPROFILE')
1078-
if (.not. allocated(home)) then
1054+
home=get_env('USERPROFILE','')
1055+
if ( home == '' ) then
10791056
call fatal_error(error, "Couldn't retrieve '%USERPROFILE%' variable")
10801057
return
10811058
end if

0 commit comments

Comments
 (0)