pathlib.f90 Source File


Files dependent on this one

sourcefile~~pathlib.f90~~AfferentGraph sourcefile~pathlib.f90 pathlib.f90 sourcefile~pathlib_windows.f90 pathlib_windows.f90 sourcefile~pathlib_windows.f90->sourcefile~pathlib.f90 sourcefile~io.f90 io.f90 sourcefile~io.f90->sourcefile~pathlib.f90 sourcefile~pathlib_unix.f90 pathlib_unix.f90 sourcefile~pathlib_unix.f90->sourcefile~pathlib.f90 sourcefile~mag_hdf5.f90 mag_hdf5.f90 sourcefile~mag_hdf5.f90->sourcefile~io.f90 sourcefile~mag.f90 mag.f90 sourcefile~mag.f90->sourcefile~io.f90 sourcefile~aurora.f90 aurora.f90 sourcefile~aurora.f90->sourcefile~io.f90 sourcefile~output.f90 output.f90 sourcefile~output.f90->sourcefile~io.f90 sourcefile~gemini.f90 gemini.f90 sourcefile~gemini.f90->sourcefile~io.f90 sourcefile~plasma.f90 plasma.f90 sourcefile~plasma.f90->sourcefile~io.f90 sourcefile~input.f90 input.f90 sourcefile~input.f90->sourcefile~io.f90 sourcefile~magcalc.f90 magcalc.f90 sourcefile~magcalc.f90->sourcefile~io.f90 sourcefile~mag_raw.f90 mag_raw.f90 sourcefile~mag_raw.f90->sourcefile~io.f90 sourcefile~mag_ncdf.f90 mag_ncdf.f90 sourcefile~mag_ncdf.f90->sourcefile~io.f90 sourcefile~plasma_output_raw.f90 plasma_output_raw.f90 sourcefile~plasma_output_raw.f90->sourcefile~plasma.f90 sourcefile~plasma_output_ncdf.f90 plasma_output_ncdf.f90 sourcefile~plasma_output_ncdf.f90->sourcefile~plasma.f90 sourcefile~plasma_input_hdf5.f90 plasma_input_hdf5.f90 sourcefile~plasma_input_hdf5.f90->sourcefile~plasma.f90 sourcefile~plasma_input_raw.f90 plasma_input_raw.f90 sourcefile~plasma_input_raw.f90->sourcefile~plasma.f90 sourcefile~plasma_output_hdf5.f90 plasma_output_hdf5.f90 sourcefile~plasma_output_hdf5.f90->sourcefile~plasma.f90 sourcefile~path_exists_intel.f90 path_exists_intel.f90 sourcefile~path_exists_intel.f90->sourcefile~input.f90 sourcefile~aurora_ncdf.f90 aurora_ncdf.f90 sourcefile~aurora_ncdf.f90->sourcefile~aurora.f90 sourcefile~path_exists.f90 path_exists.f90 sourcefile~path_exists.f90->sourcefile~input.f90 sourcefile~aurora_hdf5.f90 aurora_hdf5.f90 sourcefile~aurora_hdf5.f90->sourcefile~aurora.f90 sourcefile~aurora_raw.f90 aurora_raw.f90 sourcefile~aurora_raw.f90->sourcefile~aurora.f90

Contents

Source Code


Source Code

module pathlib

use, intrinsic:: iso_fortran_env, only: stderr=>error_unit

implicit none
private
public :: mkdir, copyfile, expanduser, home, filesep_swap

interface
module integer function copyfile(source, dest) result(istat)
character(*), intent(in) :: source, dest
end function copyfile

module integer function mkdir(path) result(istat)
character(*), intent(in) :: path
end function mkdir
end interface

contains

function filesep_swap(path) result(swapped)
!! swaps '/' to '\' for Windows systems

character(*), intent(in) :: path
character(len(path)) :: swapped
integer :: i

swapped = path
do
  i = index(swapped, '/')
  if (i == 0) exit
  swapped(i:i) = char(92)
end do

end function filesep_swap


function expanduser(indir)
!! resolve home directory as Fortran does not understand tilde
!! works for Linux, Mac, Windows, etc.
character(:), allocatable :: expanduser, homedir
character(*), intent(in) :: indir

if (len_trim(indir) < 1 .or. indir(1:1) /= '~') then
  !! nothing to expand
  expanduser = trim(adjustl(indir))
  return
endif

homedir = home()
if (len_trim(homedir) == 0) then
  !! could not determine the home directory
  expanduser = trim(adjustl(indir))
  return
endif

if (len_trim(indir) < 3) then
  !! ~ or ~/
  expanduser = homedir
else
  !! ~/...
  expanduser = homedir // trim(adjustl(indir(3:)))
endif

end function expanduser


function home()
!! https://en.wikipedia.org/wiki/Home_directory#Default_home_directory_per_operating_system
character(:), allocatable :: home, var
character(256) :: buf
integer :: L, istat

call get_environment_variable("HOME", buf, length=L, status=istat)
if (L==0 .or. istat /= 0) then
  call get_environment_variable("USERPROFILE", buf, length=L, status=istat)
endif

if (L==0 .or. istat /= 0) then
  write(stderr,*) 'ERROR: could not determine home directory from env var ',var
  if (istat==1) write(stderr,*) 'env var ',var,' does not exist.'
  home = ""
else
  home = trim(buf) // '/'
endif

end function home

end module pathlib