Skip to content

Commit

Permalink
feat(io): Add exists function for checking file or directory existence
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha committed Aug 14, 2024
1 parent 91dcc50 commit 5d4fb58
Show file tree
Hide file tree
Showing 8 changed files with 143 additions and 0 deletions.
3 changes: 3 additions & 0 deletions API-doc-FORD-file.md
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,9 @@ exclude: src/stdlib_linalg_lapack.fypp
src/stdlib_linalg_lapack_w.fypp
src/stdlib_linalg_lapack_z.fypp
fpp_extensions: fypp
extensions: f90
F90
fypp
preprocess: true
macro: MAXRANK=3
PROJECT_VERSION_MAJOR=0
Expand Down
29 changes: 29 additions & 0 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -260,3 +260,32 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module.
```fortran
{!example/io/example_fmt_constants.f90!}
```

## `exists`

### Status

Experimental

### Description

Check if a file or directory exists.
Returns `.true.` if the file or directory exists, `.false.` otherwise.

### Syntax

`exists = ` [[stdlib_io_path(module):exists(function)]] `(path)`

### Arguments

`path`: Shall be a character expression containing the path to the file or directory to check.

### Return value

The result is a scalar of type `logical`. `.true.` if the file or directory exists, `.false.` otherwise.

### Example

```fortran
{!example/io/example_exists.f90!}
```
1 change: 1 addition & 0 deletions example/io/CMakeLists.txt
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
ADD_EXAMPLE(exists)
ADD_EXAMPLE(fmt_constants)
#ADD_EXAMPLE(getline)
ADD_EXAMPLE(loadnpy)
Expand Down
14 changes: 14 additions & 0 deletions example/io/example_exists.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,14 @@
program example_exists

use stdlib_io_path, only: exists
implicit none
integer :: fh

open (newunit=fh, file='example_exists.txt')
print *, exists('example_exists.txt') ! .true.
close (fh, status="delete")

print *, exists('example_exists.txt') ! .false.
print *, exists('./doc/specs/') ! Check if directory exists

end program example_exists
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ set(SRC
stdlib_hashmaps.f90
stdlib_hashmap_chaining.f90
stdlib_hashmap_open.f90
stdlib_io_path.F90
stdlib_logger.f90
stdlib_sorting_radix_sort.f90
stdlib_system.F90
Expand Down
30 changes: 30 additions & 0 deletions src/stdlib_io_path.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
! SPDX-Identifier: MIT

!> This module implements some useful functions on pathnames.
!> To read or write files see [open()](../page/specs/stdlib_io.html#open),
!> and for accessing the filesystem see the [os](../page/specs/stdlib_io.html) module.
!> ([Specification](../page/specs/stdlib_io.html))
module stdlib_io_path

implicit none
private

public :: exists

contains

!> Version: experimental
!>
!> Check if a file or directory exists
!> ([Specification](../page/specs/stdlib_io.html#exists))
logical function exists(path)
character(len=*), intent(in) :: path

inquire (file=path, exist=exists)
#ifdef __INTEL_COMPILER
if (.not. exists) inquire (directory=path, exist=exists)
#endif

end function exists

end module stdlib_io_path
1 change: 1 addition & 0 deletions test/io/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -16,4 +16,5 @@ set_tests_properties(savetxt_qp PROPERTIES LABELS quadruple_precision)
ADDTEST(getline)
ADDTEST(npy)
ADDTEST(open)
ADDTEST(path)
ADDTEST(parse_mode)
64 changes: 64 additions & 0 deletions test/io/test_path.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,64 @@
module test_path

use stdlib_io_path, only: exists
use testdrive, only: new_unittest, unittest_type, error_type, check
implicit none
private

public :: collect_path

contains

!> Collect all exported unit tests
subroutine collect_path(testsuite)
!> Collection of tests
type(unittest_type), allocatable, intent(out) :: testsuite(:)

testsuite = [ &
new_unittest("path_exists", test_path_exists) &
]

end subroutine collect_path

subroutine test_path_exists(error)
!> Error handling
type(error_type), allocatable, intent(out) :: error
integer :: fh

open (newunit=fh, file='test_path_exists.txt')
call check(error, exists('test_path_exists.txt'))
close (fh, status="delete")

call check(error,.not. exists('test_path_exists.txt.not'))

end subroutine test_path_exists

end module test_path

program tester

use, intrinsic :: iso_fortran_env, only: error_unit
use testdrive, only: run_testsuite, new_testsuite, testsuite_type
use test_path, only: collect_path
implicit none
integer :: stat, is
type(testsuite_type), allocatable :: testsuites(:)
character(len=*), parameter :: fmt = '("#", *(1x, a))'

stat = 0

testsuites = [ &
new_testsuite("path", collect_path) &
]

do is = 1, size(testsuites)
write (error_unit, fmt) "Testing:", testsuites(is)%name
call run_testsuite(testsuites(is)%collect, error_unit, stat)
end do

if (stat > 0) then
write (error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
error stop
end if

end program tester

0 comments on commit 5d4fb58

Please sign in to comment.