Skip to content

Commit 95b47ec

Browse files
committed
is_regular_file -> is_file
1 parent 029860f commit 95b47ec

File tree

6 files changed

+41
-41
lines changed

6 files changed

+41
-41
lines changed

doc/specs/stdlib_system.md

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -497,7 +497,7 @@ Formats all the arguments into a nice error message, utilizing the constructor o
497497

498498
---
499499

500-
## `is_regular_file` - Test if a path is a regular file
500+
## `is_file` - Test if a path is a regular file
501501

502502
### Status
503503

@@ -511,7 +511,7 @@ It is designed to work across multiple platforms. On Windows, paths with both fo
511511

512512
### Syntax
513513

514-
`result = ` [[stdlib_system(module):is_regular_file(function)]]`(path)`
514+
`result = ` [[stdlib_system(module):is_file(function)]]`(path)`
515515

516516
### Class
517517

@@ -531,7 +531,7 @@ The function returns a `logical` value:
531531
### Example
532532

533533
```fortran
534-
{!example/system/example_is_regular_file.f90!}
534+
{!example/system/example_is_file.f90!}
535535
```
536536

537537
---
@@ -584,7 +584,7 @@ Experimental
584584
### Description
585585

586586
This function checks if a specified file system path is a symbolic link to either a file or a directory.
587-
Use [[stdlib_system(module):is_regular_file(function)]] and [[stdlib_system(module):is_directory(function)]] functions
587+
Use [[stdlib_system(module):is_file(function)]] and [[stdlib_system(module):is_directory(function)]] functions
588588
to check further if the link is to a file or a directory respectively.
589589
It is designed to work across multiple platforms. On Windows, paths with both forward `/` and backward `\` slashes are accepted.
590590

example/system/CMakeLists.txt

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,6 @@ ADD_EXAMPLE(make_directory)
1919
ADD_EXAMPLE(remove_directory)
2020
ADD_EXAMPLE(cwd)
2121
ADD_EXAMPLE(exists)
22-
ADD_EXAMPLE(is_regular_file)
22+
ADD_EXAMPLE(is_file)
2323
ADD_EXAMPLE(is_directory)
2424
ADD_EXAMPLE(is_symlink)
Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,14 @@
1-
! Demonstrate usage of `is_regular_file`
2-
program example_is_regular_file
3-
use stdlib_system, only: is_regular_file
1+
! Demonstrate usage of `is_file`
2+
program example_is_file
3+
use stdlib_system, only: is_file
44
implicit none
55

66
character(*), parameter :: path = "path/to/check"
77

88
! Test if path is a regular file
9-
if (is_regular_file(path)) then
9+
if (is_file(path)) then
1010
print *, "The specified path is a regular file."
1111
else
1212
print *, "The specified path is not a regular file."
1313
end if
14-
end program example_is_regular_file
14+
end program example_is_file

src/stdlib_system.F90

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -292,7 +292,7 @@ module stdlib_system
292292
!! version: experimental
293293
!!
294294
!! Tests if a given path is a regular file.
295-
!! ([Specification](../page/specs/stdlib_system.html#is_regular_file))
295+
!! ([Specification](../page/specs/stdlib_system.html#is_file))
296296
!!
297297
!!### Summary
298298
!! Function to evaluate whether a specified path corresponds to a regular file.
@@ -304,7 +304,7 @@ module stdlib_system
304304
!! It is cross-platform and utilizes native system calls.
305305
!! It supports common operating systems such as Linux, macOS, Windows, and various UNIX-like environments.
306306
!!
307-
public :: is_regular_file
307+
public :: is_file
308308

309309
! CPU clock ticks storage
310310
integer, parameter, private :: TICKS = int64
@@ -1333,18 +1333,18 @@ end function is_symlink
13331333

13341334
! checks if path is a regular file.
13351335
! It follows symbolic links and returns the status of the `target`.
1336-
logical function is_regular_file(path)
1336+
logical function is_file(path)
13371337
character(len=*), intent(in) :: path
13381338

13391339
interface
1340-
logical(c_bool) function stdlib_is_regular_file(path) bind(C, name='stdlib_is_regular_file')
1340+
logical(c_bool) function stdlib_is_file(path) bind(C, name='stdlib_is_file')
13411341
import c_char, c_bool
13421342
character(kind=c_char) :: path(*)
1343-
end function stdlib_is_regular_file
1343+
end function stdlib_is_file
13441344
end interface
13451345

1346-
is_regular_file = logical(stdlib_is_regular_file(to_c_char(trim(path))))
1347-
end function is_regular_file
1346+
is_file = logical(stdlib_is_file(to_c_char(trim(path))))
1347+
end function is_file
13481348

13491349
character function path_sep()
13501350
if (OS_TYPE() == OS_WINDOWS) then

src/stdlib_system.c

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ int stdlib_exists(const char* path, int* stat){
168168

169169
// `stat` and `_stat` follow symlinks automatically.
170170
// so no need for winapi functions.
171-
bool stdlib_is_regular_file(const char* path) {
171+
bool stdlib_is_file(const char* path) {
172172
#ifdef _WIN32
173173
struct _stat buf = {0};
174174
return _stat(path, &buf) == 0 && S_ISREG(buf.st_mode);

test/system/test_filesystem.f90

Lines changed: 23 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,8 @@ module test_filesystem
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
33
use stdlib_system, only: is_directory, delete_file, FS_ERROR, FS_ERROR_CODE, &
44
make_directory, remove_directory, make_directory_all, is_windows, OS_TYPE, &
5-
OS_WINDOWS, get_cwd, set_cwd, operator(/), exists, fs_type_unknown, &
6-
fs_type_regular_file, fs_type_directory, fs_type_symlink, is_regular_file
5+
OS_WINDOWS, get_cwd, set_cwd, operator(/), exists, fs_type_unknown, &
6+
fs_type_regular_file, fs_type_directory, fs_type_symlink, is_file
77
use stdlib_error, only: state_type, STDLIB_FS_ERROR
88
use stdlib_strings, only: to_string
99

@@ -22,18 +22,18 @@ subroutine collect_suite(testsuite)
2222
new_unittest("fs_exists_reg_file", test_exists_reg_file), &
2323
new_unittest("fs_exists_dir", test_exists_dir), &
2424
new_unittest("fs_exists_symlink", test_exists_symlink), &
25-
new_unittest("fs_is_regular_file", test_is_regular_file), &
25+
new_unittest("fs_is_file", test_is_file), &
2626
new_unittest("fs_is_directory_dir", test_is_directory_dir), &
2727
new_unittest("fs_is_directory_file", test_is_directory_file), &
2828
new_unittest("fs_delete_non_existent", test_delete_file_non_existent), &
2929
new_unittest("fs_delete_existing_file", test_delete_file_existing), &
30-
new_unittest("fs_delete_file_being_dir", test_delete_directory), &
31-
new_unittest("fs_make_dir", test_make_directory), &
32-
new_unittest("fs_make_dir_existing_dir", test_make_directory_existing), &
33-
new_unittest("fs_make_dir_all", test_make_directory_all), &
34-
new_unittest("fs_remove_dir", test_remove_directory), &
35-
new_unittest("fs_remove_dir_non_existent", test_remove_directory_nonexistent), &
36-
new_unittest("fs_cwd", test_cwd) &
30+
new_unittest("fs_delete_file_being_dir", test_delete_directory), &
31+
new_unittest("fs_make_dir", test_make_directory), &
32+
new_unittest("fs_make_dir_existing_dir", test_make_directory_existing), &
33+
new_unittest("fs_make_dir_all", test_make_directory_all), &
34+
new_unittest("fs_remove_dir", test_remove_directory), &
35+
new_unittest("fs_remove_dir_non_existent", test_remove_directory_nonexistent), &
36+
new_unittest("fs_cwd", test_cwd) &
3737
]
3838
end subroutine collect_suite
3939

@@ -108,23 +108,23 @@ subroutine test_exists_reg_file(error)
108108
if (allocated(error)) return
109109
end subroutine test_exists_reg_file
110110

111-
subroutine test_is_regular_file(error)
111+
subroutine test_is_file(error)
112112
type(error_type), allocatable, intent(out) :: error
113113
character(len=256) :: filename
114114
integer :: ios, iunit
115115
character(len=512) :: msg
116116

117-
logical :: is_file
117+
logical :: is_reg_file
118118

119119
filename = "test_file.txt"
120120

121121
! Create a file
122122
open(newunit=iunit, file=filename, status="replace", iostat=ios, iomsg=msg)
123-
call check(error, ios == 0, "Cannot init test_is_regular_file: " // trim(msg))
123+
call check(error, ios == 0, "Cannot init test_is_file: " // trim(msg))
124124
if (allocated(error)) return
125125

126-
is_file = is_regular_file(filename)
127-
call check(error, is_file, "is_regular_file could not identify a file")
126+
is_reg_file = is_file(filename)
127+
call check(error, is_reg_file, "is_file could not identify a file")
128128

129129
if (allocated(error)) then
130130
! Clean up: remove the file
@@ -137,7 +137,7 @@ subroutine test_is_regular_file(error)
137137
close(iunit,status='delete',iostat=ios,iomsg=msg)
138138
call check(error, ios == 0, "Cannot delete test file: " // trim(msg))
139139
if (allocated(error)) return
140-
end subroutine test_is_regular_file
140+
end subroutine test_is_file
141141

142142
subroutine test_exists_dir(error)
143143
type(error_type), allocatable, intent(out) :: error
@@ -293,7 +293,7 @@ subroutine test_is_directory_file(error)
293293
! Create a file
294294
open(newunit=iunit, file=filename, status="replace", iostat=ios, iomsg=msg)
295295
call check(error, ios == 0, "Cannot create test file: " // trim(msg))
296-
if (allocated(error)) return
296+
if (allocated(error)) return
297297

298298
! Verify `is_directory` identifies it as not a directory
299299
result = is_directory(filename)
@@ -303,7 +303,7 @@ subroutine test_is_directory_file(error)
303303
! Clean up: remove the file
304304
close(iunit,status='delete',iostat=ios,iomsg=msg)
305305
call check(error, ios == 0, "Cannot delete test file: " // trim(msg))
306-
if (allocated(error)) return
306+
if (allocated(error)) return
307307

308308
end subroutine test_is_directory_file
309309

@@ -378,10 +378,10 @@ subroutine test_delete_directory(error)
378378
! Clean up: remove the empty directory
379379
call execute_command_line('rmdir ' // filename, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
380380
call check(error, ios==0 .and. iocmd==0, 'Cannot cleanup delete_directory test: '//trim(msg))
381-
if (allocated(error)) return
381+
if (allocated(error)) return
382382

383383
end subroutine test_delete_directory
384-
384+
385385
subroutine test_make_directory(error)
386386
type(error_type), allocatable, intent(out) :: error
387387
type(state_type) :: err
@@ -471,7 +471,7 @@ subroutine test_remove_directory(error)
471471
call remove_directory(dir_name, err)
472472
call check(error, err%ok(), 'Could not remove directory: '//err%print())
473473

474-
if (allocated(error)) then
474+
if (allocated(error)) then
475475
! clean up: remove the empty directory
476476
call execute_command_line('rmdir ' // dir_name, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
477477
call check(error, ios==0 .and. iocmd==0, error%message // ' and cannot cleanup make_directory test: '//trim(msg))
@@ -518,14 +518,14 @@ subroutine test_cwd(error)
518518
call check(error, err%ok(), 'Could not get current working directory: '//err%print())
519519
if (allocated(error)) return
520520

521-
call check(error, pwd2 == abs_dir_name, 'Working directory is wrong, &
521+
call check(error, pwd2 == abs_dir_name, 'Working directory is wrong, &
522522
& expected: '//abs_dir_name//" got: "//pwd2)
523523
if (allocated(error)) return
524524

525525
! cleanup: set the cwd back to the initial value
526526
call set_cwd(pwd1, err)
527527
call check(error, err%ok(), 'Could not clean up cwd test, could not set the cwd back: '//err%print())
528-
if (allocated(error)) then
528+
if (allocated(error)) then
529529
! our cwd now is `./test_directory`
530530
! there is no way of removing the empty test directory
531531
return

0 commit comments

Comments
 (0)