Skip to content

Navigation Menu

Sign in
Appearance settings

Search code, repositories, users, issues, pull requests...

Provide feedback

We read every piece of feedback, and take your input very seriously.

Saved searches

Use saved searches to filter your results more quickly

Sign up
Appearance settings

Commit a2fadac

Browse files
authored
filesystem: FS_ERROR helper functions (#1015)
2 parents a0d9e22 + 873bb75 commit a2fadac

File tree

5 files changed

+173
-3
lines changed

5 files changed

+173
-3
lines changed

‎doc/specs/stdlib_system.md

Lines changed: 79 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -418,6 +418,85 @@ Returns one of the `integer` `OS_*` parameters representing the OS type, from th
418418

419419
---
420420

421+
## `FS_ERROR` - Helper function for error handling
422+
423+
### Status
424+
425+
Experimental
426+
427+
### Description
428+
429+
A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
430+
431+
### Syntax
432+
433+
`err = FS_ERROR([a1,a2,a3,a4...... a20])`
434+
435+
### Class
436+
Pure Function
437+
438+
### Arguments
439+
440+
`a1,a2,a3.....a20`(optional): They are of type `class(*), dimension(..), optional, intent(in)`.
441+
An arbitrary list of `integer`, `real`, `complex`, `character` or `string_type` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
442+
443+
### Behavior
444+
445+
Formats all the arguments into a nice error message, utilizing the constructor of [[stdlib_system(module):state_type(type)]]
446+
447+
### Return values
448+
449+
`type(state_type)`
450+
451+
### Example
452+
453+
```fortran
454+
{!example/system/example_fs_error.f90!}
455+
```
456+
457+
---
458+
459+
## `FS_ERROR_CODE` - Helper function for error handling (with error code)
460+
461+
### Status
462+
463+
Experimental
464+
465+
### Description
466+
467+
A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
468+
It also formats and prefixes the `code` passed to it as the first argument.
469+
470+
### Syntax
471+
472+
`err = FS_ERROR_CODE(code [, a1,a2,a3,a4...... a19])`
473+
474+
### Class
475+
Pure Function
476+
477+
### Arguments
478+
479+
`code`: An `integer` code.
480+
481+
`a1,a2,a3.....a19`(optional): They are of type `class(*), dimension(..), optional, intent(in)`.
482+
An arbitrary list of `integer`, `real`, `complex`, `character` or `string_type` variables. Numeric variables may be provided as either scalars or rank-1 (array) inputs.
483+
484+
### Behavior
485+
486+
Formats all the arguments into a nice error message, utilizing the constructor of [[stdlib_system(module):state_type(type)]]
487+
488+
### Return values
489+
490+
`type(state_type)`
491+
492+
### Example
493+
494+
```fortran
495+
{!example/system/example_fs_error.f90!}
496+
```
497+
498+
---
499+
421500
## `is_directory` - Test if a path is a directory
422501

423502
### Status

‎example/system/CMakeLists.txt

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,9 @@ ADD_EXAMPLE(process_5)
1111
ADD_EXAMPLE(process_6)
1212
ADD_EXAMPLE(process_7)
1313
ADD_EXAMPLE(sleep)
14+
ADD_EXAMPLE(fs_error)
1415
ADD_EXAMPLE(path_join)
1516
ADD_EXAMPLE(path_split_path)
1617
ADD_EXAMPLE(path_base_name)
1718
ADD_EXAMPLE(path_dir_name)
19+

‎example/system/example_fs_error.f90

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
! Demonstrate usage of `FS_ERROR`, `FS_ERROR_CODE`
2+
program example_fs_error
3+
use stdlib_system, only: FS_ERROR, FS_ERROR_CODE
4+
use stdlib_error, only: state_type, STDLIB_FS_ERROR
5+
implicit none
6+
7+
type(state_type) :: err0, err1
8+
9+
err0 = FS_ERROR("Could not create directory", "`temp.dir`", "- Already exists")
10+
11+
if (err0%state == STDLIB_FS_ERROR) then
12+
! Error encountered: Filesystem Error: Could not create directory `temp.dir` - Already exists
13+
print *, err0%print()
14+
end if
15+
16+
err1 = FS_ERROR_CODE(1, "Could not create directory", "`temp.dir`", "- Already exists")
17+
18+
if (err1%state == STDLIB_FS_ERROR) then
19+
! Error encountered: Filesystem Error: code - 1, Could not create directory `temp.dir` - Already exists
20+
print *, err1%print()
21+
end if
22+
23+
end program example_fs_error

‎src/stdlib_system.F90

Lines changed: 46 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module stdlib_system
22
use, intrinsic :: iso_c_binding, only : c_int, c_long, c_ptr, c_null_ptr, c_int64_t, c_size_t, &
33
c_f_pointer
44
use stdlib_kinds, only: int64, dp, c_bool, c_char
5-
use stdlib_strings, only: to_c_char
5+
use stdlib_strings, only: to_c_char, to_string
66
use stdlib_string_type, only: string_type
77
use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
88
implicit none
@@ -142,6 +142,21 @@ module stdlib_system
142142
!! On Windows, this is `NUL`. On UNIX-like systems, this is `/dev/null`.
143143
!!
144144
public :: null_device
145+
146+
!! version: experimental
147+
!!
148+
!! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
149+
!! ([Specification](../page/specs/stdlib_system.html#FS_ERROR))
150+
!!
151+
public :: FS_ERROR
152+
153+
!! version: experimental
154+
!!
155+
!! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
156+
!! It also formats and prefixes the `code` passed to it as the first argument
157+
!! ([Specification](../page/specs/stdlib_system.html#FS_ERROR_CODE))
158+
!!
159+
public :: FS_ERROR_CODE
145160

146161
! CPU clock ticks storage
147162
integer, parameter, private :: TICKS = int64
@@ -914,6 +929,36 @@ subroutine delete_file(path, err)
914929
end if
915930
end subroutine delete_file
916931

932+
pure function FS_ERROR_CODE(code,a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
933+
a11,a12,a13,a14,a15,a16,a17,a18,a19) result(state)
934+
935+
type(state_type) :: state
936+
!> Platform specific error code
937+
integer, intent(in) :: code
938+
!> Optional rank-agnostic arguments
939+
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
940+
a11,a12,a13,a14,a15,a16,a17,a18,a19
941+
942+
character(32) :: code_msg
943+
944+
write(code_msg, "('code - ', i0, ',')") code
945+
946+
state = state_type(STDLIB_FS_ERROR, code_msg,a1,a2,a3,a4,a5,a6,a7,a8,&
947+
a9,a10,a11,a12,a13,a14,a15,a16,a17,a18,a19)
948+
end function FS_ERROR_CODE
949+
950+
pure function FS_ERROR(a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,&
951+
a12,a13,a14,a15,a16,a17,a18,a19,a20) result(state)
952+
953+
type(state_type) :: state
954+
!> Optional rank-agnostic arguments
955+
class(*), intent(in), optional, dimension(..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,&
956+
a11,a12,a13,a14,a15,a16,a17,a18,a19,a20
957+
958+
state = state_type(STDLIB_FS_ERROR, a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12,&
959+
a13,a14,a15,a16,a17,a18,a19,a20)
960+
end function FS_ERROR
961+
917962
character function path_sep()
918963
if (OS_TYPE() == OS_WINDOWS) then
919964
path_sep = '\'

‎test/system/test_filesystem.f90

Lines changed: 23 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module test_filesystem
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3-
use stdlib_system, only: is_directory, delete_file
4-
use stdlib_error, only: state_type
3+
use stdlib_system, only: is_directory, delete_file, FS_ERROR, FS_ERROR_CODE
4+
use stdlib_error, only: state_type, STDLIB_FS_ERROR
55

66
implicit none
77

@@ -13,6 +13,7 @@ subroutine collect_suite(testsuite)
1313
type(unittest_type), allocatable, intent(out) :: testsuite(:)
1414

1515
testsuite = [ &
16+
new_unittest("fs_error", test_fs_error), &
1617
new_unittest("fs_is_directory_dir", test_is_directory_dir), &
1718
new_unittest("fs_is_directory_file", test_is_directory_file), &
1819
new_unittest("fs_delete_non_existent", test_delete_file_non_existent), &
@@ -21,6 +22,26 @@ subroutine collect_suite(testsuite)
2122
]
2223
end subroutine collect_suite
2324

25+
subroutine test_fs_error(error)
26+
type(error_type), allocatable, intent(out) :: error
27+
type(state_type) :: s1, s2
28+
character(:), allocatable :: msg
29+
30+
msg = "code - 10, Cannot create File temp.txt - File already exists"
31+
s1 = FS_ERROR_CODE(10, "Cannot create File temp.txt -", "File already exists")
32+
33+
call check(error, s1%state == STDLIB_FS_ERROR .and. s1%message == msg, &
34+
"FS_ERROR_CODE: Could not construct the state with code correctly")
35+
if (allocated(error)) return
36+
37+
msg = "Cannot create File temp.txt - File already exists"
38+
s2 = FS_ERROR("Cannot create File temp.txt -", "File already exists")
39+
40+
call check(error, s2%state == STDLIB_FS_ERROR .and. s2%message == msg, &
41+
"FS_ERROR: Could not construct state without code correctly")
42+
if (allocated(error)) return
43+
end subroutine test_fs_error
44+
2445
! Test `is_directory` for a directory
2546
subroutine test_is_directory_dir(error)
2647
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
(0)

AltStyle によって変換されたページ (->オリジナル) /