Hi,
With INQUIRE, I can check if a file exists. How do I do the same for a directory?
Regards,
Arjan
Hi,
With INQUIRE, I can check if a file exists. How do I do the same for a directory?
Regards,
Arjan
From a 2007 answer on the Intel Fortran forum:
So, there is no Fortran standard way to ask if a directory exists.(Ignoring for now that even the syntax for directories is non-portable.) The closest you can come is the POSIX routine PXFOPENDIR which opens a directory. For compilers that support the POSIX Fortran library, this should be reasonably portable.
I also found a couple suggestions on StackOverflow (but none are really definitive): Test whether a directory exists or not
One option I’m aware of is the Fortran filesystem library, which effectively wraps the C++17 filesystem library. An example would look like:
use filesystem, only : path_t
type(path_t) :: p
p = path_t("my/path")
print *, p%exists() .and. p%is_dir()
Another option would be the is_dir
function from the fpm_filesystem
module:
This should be as simple as,
use fpm_filesystem, only: is_dir
print *, is_dir("my/path")
In this Open PR for stdlib Add filesystem interaction by minhqdao · Pull Request #874 · fortran-lang/stdlib · GitHub @minhdao is working on several functionalities for file system interaction among which a “exists” function for files and paths. From here I learned that Intel Fortran enables using inquire
with a directory argument https://www.intel.com/content/www/us/en/docs/fortran-compiler/developer-guide-reference/2023-2/inquire.html
A Fortran-only “solution” might be:
There is OS dependence in this. On windows I pass the file entity string to GetFileAttributes and the iand(attrib,FILE_ATTRIBUTE_DIRECTORY) > 0 tells you it is a folder. I should add those are windows sdk things in say IFWIN on intel fortran.
Not a pure Fortran solution but the following appears to work on my Linux systems. Not sure about Windows.
C code that uses opendir() to test for a directory. Taken from stackoverflow post.
/* dir_exists.c */
#include <dirent.h>
#include <errno.h>
extern int dir_exists(const char *dir_path)
{
/* code taken from stackoverflow post */
DIR* dir = opendir(dir_path);
if (dir) {
/* Directory exists. */
closedir(dir);
return 0;
} else if (ENOENT == errno) {
return 1;
/* Directory does not exist. */
} else {
return -1;
/* opendir() failed for some other reason. */
}
}
check_dir function that wraps dir_exists and test program.
Program test_dir
Implicit NONE
Character(:), Allocatable :: lib_path
Character(:), Allocatable :: nodir_path
! Check for non-existent dir
lib_path = "/usr/lib64"
nodir_path = "/usr/somedir"
If (check_dir(lib_path)) Then
Print *, TRIM(ADJUSTL(lib_path))//" exists"
Else
Print *, TRIM(ADJUSTL(lib_path))//" doesn't exist"
End If
If (check_dir(nodir_path)) Then
Print *, TRIM(ADJUSTL(nodir_path))//" exists"
Else
Print *, TRIM(ADJUSTL(nodir_path))//" doesn't exist"
End If
Contains
Logical Function check_dir(dir_path)
USE ISO_C_BINDING, ONLY: C_INT, C_CHAR, C_NULL_CHAR
Implicit NONE
Character(*), Intent(IN) :: dir_path
Interface
Function c_dir_exists(dir_path) BIND(C,NAME="dir_exists")
IMPORT :: C_INT, C_CHAR
Character(KIND=C_CHAR), Intent(IN) :: dir_path(*)
Integer(C_INT) :: c_dir_exists
End Function c_dir_exists
End Interface
Character(:), ALLOCATABLE :: c_path
c_path = TRIM(ADJUSTL(dir_path))//C_NULL_CHAR
check_dir = (c_dir_exists(c_path) == 0_C_INT)
End Function check_dir
End Program test_dir
Windows does not have dirent but you can always add it through this project: dirent
Another solution for Linux/FreeBSD, using the fortran-unix bindings:
logical function is_dir(path)
use :: unix
character(len=*), intent(in) :: path
integer :: file_type, stat
integer(kind=c_int64_t) :: mode
type(c_stat_type) :: fs
is_dir = .false.
stat = c_stat(trim(path) // c_null_char, fs)
if (stat /= 0) return
mode = c_uint32_to_int64(fs%st_mode)
file_type = int(iand(mode, int(S_IFMT, kind=c_int64_t)))
is_dir = (file_type == S_IFDIR)
end function is_dir
When using Windows, I would try to create a file in the directory. If it works then ok, otherwise there is a problem; most likely the directory does not exist or is not available.
I mainly use local windows drives, so this approach works for my experience.
Alternatively, you can create a binding to GetFileAttributes. You can then check if the return value equals FILE_ATTRIBUTE_DIRECTORY 16 (0x00000010)
There is no standard intrinsic or statement to determine if a pathname is a directory.
The answer varies depending on how portable the solution has to be.
o is it only needed in Microsoft environments?
o is it only needed in POSIX environments?
o is there always a shell of the same brand available, like POSIX shells (sh,bash,ksh,…)?
o is it only needed for a particular compiler?
o some compilers have an extension intrinsic, typically called ISDIR().
o in a POSIX environment it is easy to use a little C wrapper to isolate you from
whether C is implementing some functionality as a macro or not that you can then
call.
o there are often commands you can call with EXECUTE_COMMAND_LINE like
the Bourne shell “test” command, where the exit status of the command
can be used to determine many properties.
In addition to what has been mentioned, note
In a POSIX environment the github repositories (available via fpm(1)) have
several alternatives, such as system_isdir() and is_dir(). Both repositories
and code have extensive help text.
[dependencies]
M_path = { git = "https://github.com/urbanjost/M_path.git" }
M_system = { git = "https://github.com/urbanjost/M_system.git" }
The fpm command has both an example of using system commands (is_dir) and using a C interface
(c_is_dir).
Depending on the compiler(s) you are using, see if the ISDIR() extension is present.
With unix/posix type file systems, a directory is just a special kind of file, so you can test for the existence of a directory the same way you test a file. Here is a toy program that demonstrates this:
program dir
character(255) :: dname = '/'
logical :: dexist = .false.
character(*), parameter :: cfmt='(*(g0))'
write(*,cfmt) 'input the directory name:'
read(*,'(a)') dname
write(*,cfmt) 'testing for existence of ', trim(dname)
inquire( file=dname, exist=dexist )
write(*,cfmt) 'exist=', dexist
end program dir
$ gfortran dir.f90 && a.out
input the directory name:
./none
testing for existence of ./none
exist=F
$ a.out
input the directory name:
../work
testing for existence of ../work
exist=T
There is no file or directory in my cwd called ./none
, so the above is correct. My cwd is ../work
, so that directory does exist. Notice that ./
and ../
work for relative file names as expected because those are file system entries, not shell variables. If you do want to use a shell variable, then it must be translated first with the GET_ENVIRONMENT_VARIABLE()
intrinsic.
If you want to distinguish between a file and a directory, then the other posts in this thread show how to do that. That is operating system specific and goes beyond standard fortran. But if you know already the name of the directory, and that it is indeed a directory and not a regular file, then you can test for it with just standard fortran as above.
INQUIRE() should also work for directories with ifx: https://www.intel.com/content/www/us/en/docs/fortran-compiler/developer-guide-reference/2024-2/obtain-file-information-inquire-statement.html
Thanks! This is a great, albeit non-portable, solution. It would be very nice if INQUIRE(DIRECTORY=
would find its way into the standard.