Skip to content

Commit 42c839c

Browse files
committed
add functions, parameters
1 parent 60f5308 commit 42c839c

File tree

1 file changed

+72
-4
lines changed

1 file changed

+72
-4
lines changed

src/stdlib_system.F90

Lines changed: 72 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -204,6 +204,44 @@ module stdlib_system
204204
!! ([Specification](../page/specs/stdlib_system.html#FS_ERROR_CODE))
205205
!!
206206
public :: FS_ERROR_CODE
207+
208+
!> Version: experimental
209+
!>
210+
!> Integer constants representing the most common path types.
211+
!> ([Specification](../page/specs/stdlib_system.html))
212+
integer, parameter, public :: &
213+
!> Represents an unknown path type
214+
type_unknown = 0, &
215+
!> Represents a regular file
216+
type_regular_file = 1, &
217+
!> Represents a directory
218+
type_directory = 2, &
219+
!> Represents a symbolic link
220+
type_symlink = 3
221+
222+
!! version: experimental
223+
!!
224+
!! Checks if a path exists in the filesystem.
225+
!! ([Specification](../page/specs/stdlib_system.html#exists))
226+
!!
227+
!!### Summary
228+
!! Function to check whether the path exists in the fileystem at all.
229+
!! If the path does exist, returns the type of the path.
230+
!!
231+
!!### Description
232+
!!
233+
!! The function performs a system call (syscall) to the operating system, to retrieve the metadata
234+
!! corresponding to a path, and identifies the type of path it is.
235+
!! It can distinguish among the following path types
236+
!!
237+
!! - Regular File
238+
!! - Directory
239+
!! - Symbolic Link
240+
!!
241+
!! Returns a constant representing the path type or `type_unknown` if it cannot be determined.
242+
!! If there has been an error, It is handled using `state_type`.
243+
!!
244+
public :: exists
207245

208246
! CPU clock ticks storage
209247
integer, parameter, private :: TICKS = int64
@@ -899,22 +937,27 @@ end function is_directory
899937
! A helper function to get the result of the C function `strerror`.
900938
! `strerror` is a function provided by `<string.h>`.
901939
! It returns a string describing the meaning of `errno` in the C header `<errno.h>`
902-
function c_get_strerror() result(str)
940+
function c_get_strerror(winapi) result(str)
903941
character(len=:), allocatable :: str
942+
logical, optional, intent(in) :: winapi
904943

905944
interface
906-
type(c_ptr) function strerror(len) bind(C, name='stdlib_strerror')
907-
import c_size_t, c_ptr
945+
type(c_ptr) function strerror(len, winapi) bind(C, name='stdlib_strerror')
946+
import c_size_t, c_ptr, c_bool
908947
implicit none
909948
integer(c_size_t), intent(out) :: len
949+
logical, intent(in) :: winapi
910950
end function strerror
911951
end interface
912952

913953
type(c_ptr) :: c_str_ptr
914954
integer(c_size_t) :: len, i
915955
character(kind=c_char), pointer :: c_str(:)
956+
logical :: winapi_
916957

917-
c_str_ptr = strerror(len)
958+
winapi_ = optval(winapi, .false.)
959+
960+
c_str_ptr = strerror(len, winapi_)
918961

919962
call c_f_pointer(c_str_ptr, c_str, [len])
920963

@@ -1134,6 +1177,31 @@ pure function FS_ERROR(a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,&
11341177
a13,a14,a15,a16,a17,a18,a19,a20)
11351178
end function FS_ERROR
11361179

1180+
function exists(path, err) result(fs_type)
1181+
character(*), intent(in) :: path
1182+
type(state_type), optional, intent(out) :: err
1183+
integer :: fs_type
1184+
1185+
type(state_type) :: err0
1186+
1187+
interface
1188+
integer function stdlib_exists(path, stat) bind(C, name='stdlib_exists')
1189+
import c_char, c_int
1190+
character(kind=c_char), intent(in) :: path(*)
1191+
integer(kind=c_int), intent(out) :: stat
1192+
end function stdlib_exists
1193+
end interface
1194+
1195+
integer(kind=c_int) :: stat
1196+
1197+
fs_type = stdlib_exists(to_c_char(trim(path)), stat)
1198+
1199+
if (stat /= 0) then
1200+
err0 = FS_ERROR_CODE(stat, c_get_strerror())
1201+
call err0%handle(err)
1202+
end if
1203+
end function exists
1204+
11371205
character function path_sep()
11381206
if (OS_TYPE() == OS_WINDOWS) then
11391207
path_sep = '\'

0 commit comments

Comments
 (0)