aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm/installer.f9036
-rw-r--r--fpm/src/fpm_filesystem.f9023
2 files changed, 52 insertions, 7 deletions
diff --git a/fpm/src/fpm/installer.f90 b/fpm/src/fpm/installer.f90
index ddfc77b..d01bd27 100644
--- a/fpm/src/fpm/installer.f90
+++ b/fpm/src/fpm/installer.f90
@@ -7,7 +7,8 @@ module fpm_installer
use, intrinsic :: iso_fortran_env, only : output_unit
use fpm_environment, only : get_os_type, os_is_unix
use fpm_error, only : error_t, fatal_error
- use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path
+ use fpm_filesystem, only : join_path, mkdir, exists, unix_path, windows_path, &
+ env_variable
implicit none
private
@@ -109,11 +110,7 @@ contains
if (present(prefix)) then
self%prefix = prefix
else
- if (os_is_unix(self%os)) then
- self%prefix = default_prefix_unix
- else
- self%prefix = default_prefix_win
- end if
+ call set_default_prefix(self%prefix, self%os)
end if
if (present(bindir)) then
@@ -136,6 +133,33 @@ contains
end subroutine new_installer
+ !> Set the default prefix for the installation
+ subroutine set_default_prefix(prefix, os)
+ !> Installation prefix
+ character(len=:), allocatable :: prefix
+ !> Platform identifier
+ integer, intent(in), optional :: os
+
+ character(len=:), allocatable :: home
+
+ if (os_is_unix(os)) then
+ call env_variable(home, "HOME")
+ if (allocated(home)) then
+ prefix = join_path(home, ".local")
+ else
+ prefix = default_prefix_unix
+ end if
+ else
+ call env_variable(home, "APPDATA")
+ if (allocated(home)) then
+ prefix = join_path(home, "local")
+ else
+ prefix = default_prefix_win
+ end if
+ end if
+
+ end subroutine set_default_prefix
+
!> Install an executable in its correct subdirectory
subroutine install_executable(self, executable, error)
!> Instance of the installer
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index 433a75b..f221917 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -5,7 +5,7 @@ module fpm_filesystem
use fpm_strings, only: f_string, string_t, split
implicit none
private
- public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files,&
+ public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -13,6 +13,27 @@ module fpm_filesystem
contains
+subroutine env_variable(var, name)
+ character(len=:), allocatable, intent(out) :: var
+ character(len=*), intent(in) :: name
+ integer :: length, stat
+
+ call get_environment_variable(name, length=length, status=stat)
+ if (stat /= 0) return
+
+ allocate(character(len=length) :: var)
+
+ if (length > 0) then
+ call get_environment_variable(name, var, status=stat)
+ if (stat /= 0) then
+ deallocate(var)
+ return
+ end if
+ end if
+
+end subroutine env_variable
+
+
function basename(path,suffix) result (base)
! Extract filename from path with/without suffix
!