Sometimes it is useful to have the full path name, e.g. for pasting into other programs or for identifying a file unambiguously. Is there a reliable way to do this in Fortran, even resorting to system commands? It seems to me that the most natural way would be to use the inquire (unit=xxx/file=xxx, name=…, exist=) statement but the standard only requires that name= returns a filename that will open the file in a subsequent open statement. ifort conveniently returns a full path name here but nagfor and gfortran just echo the filename used to open the file. This is obviously consistent with the standard but is there a reason why these compilers are not a little more helpful? ifort also provides the non-standard function fullpathqq for this. I realize that Fortran is agnostic to the way that OS’s resolve filenames (which can be complex, e.g. in multithreaded applications) but the runtime must at some stage know the canonical file name so access to this would be useful. Various OS’s provide mechanisms for this, e.g. Windows has the dir command, and Linux and its C compiler provides readlink -f but this is not universally available in other Unix-based systems, e.g. MAC OSX.
character(len=2048) :: path
call get_command_argument(0, path)
To get the path of the executable. From there, you can resolve relative paths. To get the absolute path of arbitrary files, you probably have to resort to the OS API.
The Fortran standard isn’t of help to you here. As you note, INQUIRE requires only that the returned name be suitable for opening the file in a subsequent OPEN statement. There are usually platform-specific library routines that will get you more information.
As for @interkosmos ’ mention of get_command_argument
, the standard says that this is the command name, “if the processor has such a concept”.
This is definitely not the way to get a full file pathname. This is the path to the executable, which is entirely unrelated to the path of the working directory where the execution occurs. The two paths could even be on different file systems, or with network file systems they could be on different file servers.
As for the original question, one of the things I missed when I moved from DEC and VAX computers to other machines is that the open/close/inquire statements had separate file=
and dir=
fields. You could request both and put them together for the full path name if you wanted. Of course, that was an extension to f77, so it was not portable and I soon dropped that feature from my codes when that became important.
This is important when you want to use a temporary scratch file. In f77 and later, you can not name a scratch file, which means that the programmer has no control over where it is actually located. If standard f77 had something equivalent to dir= on the open statement, then it would have been possible to have some control over that file placement. In my kind of chemistry applications, it is important to place scratch files on specific devices, and to sometimes spread the necessary scratch files around among specific devices in order for a calculation to even be possible. Thus in my codes, I almost never use scratch files as defined by f77, I always gave them names and then closed them with status='delete'
. Fortran usually puts scratch files in /tmp. That is something that I absolutely never, not in a million years, would ever want to do with my applications. The danger is that my user job would fill up the /tmp device and crash the operating system.
If you are using Linux/Unix the following will return the path to the current directory. Don’t know if it works on Windows but the C function called (getcwd) is a POSIX function. Change the size of the string length (currently 132) to something bigger if you have abnormally long path names.
Subroutine get_current_dir(dir_name)
USE ISO_C_BINDING
Implicit NONE
Character(LEN=:), ALLOCATABLE, Intent(INOUT) :: dir_name
Type(C_PTR) :: c_str_ptr
Character(132), Pointer :: f_str_ptr
Integer :: ilen, inull
Interface
Function c_getcwd(buf, size) BIND(C, NAME="getcwd")
IMPORT :: C_PTR, C_SIZE_T
Type(C_PTR), VALUE :: buf
Integer(C_SIZE_T), VALUE :: size
Type(C_PTR) :: c_getcwd
End Function c_getcwd
End Interface
Interface
Subroutine c_free(ptr) BIND(C,name="free")
IMPORT :: C_PTR
Implicit NONE
Type(C_PTR), VALUE :: ptr
End Subroutine c_free
End Interface
c_str_ptr = c_getcwd(C_NULL_PTR, 132_C_SIZE_T)
Call C_F_POINTER(c_str_ptr, f_str_ptr)
ilen = LEN_TRIM(f_str_ptr)
inull = INDEX(f_str_ptr, C_NULL_CHAR)
If (inull /= 0) ilen = inull-1
ilen = MAX(1, MIN(ilen,132))
dir_name = TRIM(ADJUSTL(f_str_ptr(1:ilen)))
NULLIFY(f_str_ptr)
If (C_ASSOCIATED(c_str_ptr)) Then
Call c_free(c_str_ptr)
End If
End Subroutine get_current_dir
Edit, forgot that C will malloc space for string when buff is a NULL for glibc version of getcwd. Have to free it to prevent a memory leak.
The call to the C realpath routine has served me well, but I only use POSIX environments so not sure if MSWindows is an issue or not. I have one in the M_system module which is also included in the GPF (General Purpose Fortran) collection; so if you are using fpm you can just add M_system as a dependency and call system_realpath(3).
https://urbanjost.github.io/general-purpose-fortran/docs/system_realpath.3m_system.html
urbanjost/M_system: Call C system routines (mostly POSIX) from Fortran
The source code for fpm(1) has several routines including one using system commands for getting pathnames as another example.
Thanks everybody for your suggestions. The file= dir= specifiers would have been nice to standardize.
Seems like the way to go (alas) is to use the C compiler and the realpath function. I would like to use the fpm with Urbanjost’s library but I’m using Visual Studio/Intel so have never taken the time to work out how to do this. So with some searching and your suggestions, I followed Everything Functional’s video about installing the fpm extension to VS (Fortran Package Manager (fpm) for Visual Studio - YouTube). I installed that successfully. I also cloned the M_system from git.
However, I got some errors when running ‘fpm build’:
Starting fpm build
C:\Users\david\source\repos\M_system>"C:\Program Files (x86)\Intel\oneAPI\compiler\2022.1.0\env\vars.bat"
The system cannot find the batch label specified - SetVS2019NSTALLDIR
C:\Users\david\source\repos\M_system>fpm.exe build --compiler "C:\Program Files (x86)\Intel\oneAPI\compiler\2022.1.0\windows\bin\icx.exe"
'fpm.exe' is not recognized as an internal or external command, operable program or batch file.
I’m not sure if these are my errors or theirs. The first one looks like Intel’s or my installation. My environment does have
VS2019INSTALLDIR=C:\Program Files (x86)\Microsoft Visual Studio\2019\Community
VSINSTALLDIR=C:\Program Files (x86)\Microsoft Visual Studio\2019\Community\
I also could not find fpm.exe so that it looks like it has not been installed. Excuse my ignorance - without a fully working example, I do not have a clear understanding of how this all fits together.
I am also not sure how this integrates with an existing sln. What would be really helpful is to take the video forward all the way to getting a working program using a library installed with fpm. I think adding the M_system library would make an excellent example!
I am really pleased that the Fortran community is improving the working environment for Fortran developers. I have used R (for Windows) quite a lot and really like the slickness of their whole working environment - interpreter + IDE + package manager + documentation + demos, all under the close scrutiny of a core team of experts. Looks like Fortran is heading the same way and I applaud that. I think it is important.
This could probably be simplified, as there were a lot of issues with
passing strings back and forth in early implementations of iso_c_binding,
but I just extracted the parts from M_system including the demo program.
Worked on a Linux box and a Cygwin window. Did not try it anywhere else.
Click here to see example code
module M_fullpath
use,intrinsic :: iso_c_binding, only : c_ptr, C_char, c_null_char, c_size_t
use,intrinsic :: iso_c_binding, only : c_int, c_f_pointer, c_associated
contains
function system_realpath(input) result(string)
character(len=*),intent(in) :: input
type(c_ptr) :: c_output
character(len=:),allocatable :: string
character(kind=c_char,len=1),allocatable :: temp(:)
interface
function c_realpath(c_input) bind(c,name="my_realpath") result(c_buffer)
import c_char, c_size_t, c_ptr, c_int
character(kind=c_char) ,intent(in) :: c_input(*)
type(c_ptr) :: c_buffer
end function
end interface
temp = str2_carr(trim(input)) ! kludge for bug in ifort (IFORT) 2021.3.0 20210609
c_output=c_realpath(temp)
if(.not.c_associated(c_output))then
string=char(0)
else
string=C2F_string(c_output)
endif
end function system_realpath
function C2F_string(c_string_pointer) result(f_string)
! gets a C string (pointer), and returns the corresponding Fortran string up to 4096(max_len) characters;
! If the C string is null, it returns string C "null" character:
type(c_ptr), intent(in) :: c_string_pointer
character(len=:), allocatable :: f_string
character(kind=c_char), dimension(:), pointer :: char_array_pointer => null()
integer,parameter :: max_len=4096
character(len=max_len) :: aux_string
integer :: i
integer :: length
length=0
call c_f_pointer(c_string_pointer,char_array_pointer,[max_len])
if (.not.associated(char_array_pointer)) then
if(allocated(f_string))deallocate(f_string)
allocate(character(len=4)::f_string)
f_string=c_null_char
return
endif
aux_string=" "
do i=1,max_len
if (char_array_pointer(i)==c_null_char) then
length=i-1; exit
endif
aux_string(i:i)=char_array_pointer(i)
enddo
if(allocated(f_string))deallocate(f_string)
allocate(character(len=length)::f_string)
f_string=aux_string(1:length)
end function C2F_string
pure function str2_carr(string) result (array)
! ident_31="@(#)M_system::str2_carr(3fp): function copies trimmed string to null terminated char array"
character(len=*),intent(in) :: string
character(len=1,kind=c_char) :: array(len(string)+1)
integer :: i
do i = 1,len_trim(string)
array(i) = string(i:i)
enddo
array(i:i)=c_null_char
end function str2_carr
subroutine system_perror(prefix)
use, intrinsic :: iso_fortran_env, only : ERROR_UNIT, INPUT_UNIT, OUTPUT_UNIT ! access computing environment
! ident_14="@(#)M_system::system_perror(3f): call perror(3c) to display error message"
character(len=*),intent(in) :: prefix
integer :: ios
character(kind=c_char,len=1),allocatable :: temp(:)
interface
subroutine c_perror(c_prefix) bind (C,name="perror")
import c_char
character(kind=c_char) :: c_prefix(*)
end subroutine c_perror
end interface
flush(unit=ERROR_UNIT,iostat=ios)
flush(unit=OUTPUT_UNIT,iostat=ios)
flush(unit=INPUT_UNIT,iostat=ios)
temp = str2_carr(trim(prefix)) ! kludge for bug in ifort (IFORT) 2021.3.0 20210609
call c_perror(temp)
end subroutine system_perror
end module M_fullpath
#include <errno.h>
#include <limits.h>
#include <stdlib.h>
/*------------------------------------------------------------------------------------------------*/
char* my_realpath (char *symlinkpath) {
return(realpath (symlinkpath, NULL));
}
program demo_system_realpath
use M_fullpath, only : system_realpath, system_perror
implicit none
! resolve each pathname given on command line
character(len=:),allocatable :: pathi,patho
integer :: i
integer :: filename_length
do i = 1, command_argument_count()
! get pathname from command line arguments
call get_command_argument (i , length=filename_length)
if(allocated(pathi))deallocate(pathi)
allocate(character(len=filename_length) :: pathi)
call get_command_argument (i , value=pathi)
!
! resolve each pathname
patho=system_realpath(pathi)
if(patho.ne.char(0))then
write(*,*)trim(pathi),'=>',trim(patho)
else
call system_perror(&
& '*system_realpath* error for pathname '//trim(pathi)//':')
write(*,*)trim(pathi),'=>',trim(patho)
endif
* List item
deallocate(pathi)
enddo
! if there were no pathnames given resolve the pathname "."
if(i.eq.1)then
patho=system_realpath('.')
write(*,*)'.=>',trim(patho)
endif
end program demo_system_realpath
Assuming you know how to build a mixed C/Fortran code in your programming environment. No idea if realpath(3c) is available in your environment, as it sounds like it is MSWindows (?) but M_system has worked on a lot of Unix, GNU/Linux, BSD, Cygwin, WSL environments so hopefully it is there. I remember there being a DOS equivalent but do not have an example of it laying around, but should be easy to find on WWW.
On Windows there appears to be a C++ (maybe C) function called GetFullPathName but I don’t know what library its in. The getcwd function is supported but is named _getcwd. Again I don’t know what library in lives in under Windows. A web search is your friend for more info on GetFullPathName and _getcwd.
Edit.
see
That is a Windows API routine that is easily callable from Fortran. It resides in kernel32.lib, which is always linked in. Intel Fortran on Windows declares an interface to it in module KERNEL32. The description of it is at GetFullPathNameA function (fileapi.h) - Win32 apps | Microsoft Docs
Personally I have been using the POSIX ‘realpath’ and on windows the almost equivalent ‘_fullname’ with some success. It gives something like this
interface
#ifndef _WIN32
function realpath_c(path, resolved_path) result(ptr) bind(C, name="realpath")
import :: c_ptr, c_char
character(kind=c_char, len=1), intent(in) :: path(*)
character(kind=c_char, len=1), intent(out) :: resolved_path(*)
type(c_ptr) :: ptr
end function
#else
function fullpath_c(resolved_path, path, maxLength) result(ptr) bind(C, name="_fullpath")
import :: c_ptr, c_char, c_int
character(kind=c_char, len=1), intent(out) :: resolved_path(*)
character(kind=c_char, len=1), intent(in) :: path(*)
integer(c_int), value, intent(in) :: maxLength
type(c_ptr) :: ptr
end function
#endif
end interface
And in your code
function fullpath(path) result(resolved_path)
character(*), intent(in) :: path
character(:), allocatable :: resolved_path
!private
type(c_ptr) :: ptr
character(1) :: tmp(256)
integer :: idx
allocate(character(256) :: resolved_path)
#ifndef _WIN32
ptr = realpath_c(path // c_null_char, tmp)
#else
ptr = fullpath_c(tmp, path // c_null_char, 256)
#endif
resolved_path = transfer(tmp, resolved_path)
idx = index(resolved_path, c_null_char)
resolved_path = resolved_path(:idx - 1)
end function