@@ -2,7 +2,7 @@ module stdlib_system
22use , intrinsic :: iso_c_binding, only : c_int, c_long, c_ptr, c_null_ptr, c_int64_t, c_size_t, &
33 c_f_pointer
44use 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
66use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
77implicit none
88private
@@ -133,6 +133,13 @@ module stdlib_system
133133! ! On Windows, this is `NUL`. On UNIX-like systems, this is `/dev/null`.
134134! !
135135public :: null_device
136+
137+ ! ! version: experimental
138+ ! !
139+ ! ! A helper function for returning the `type(state_type)` with the flag `STDLIB_FS_ERROR` set.
140+ ! ! `FS_ERROR_CODE` also prefixes the `code` passed to it as the first argument
141+ ! !
142+ public :: FS_ERROR, FS_ERROR_CODE
136143
137144! CPU clock ticks storage
138145integer , parameter , private :: TICKS = int64
@@ -770,4 +777,30 @@ subroutine delete_file(path, err)
770777 end if
771778end subroutine delete_file
772779
780+ pure function FS_ERROR_CODE (code ,a1 ,a2 ,a3 ,a4 ,a5 ,a6 ,a7 ,a8 ,a9 ,a10 , &
781+ a11 ,a12 ,a13 ,a14 ,a15 ,a16 ,a17 ,a18 ) result(state)
782+
783+ type (state_type) :: state
784+ ! > Platform specific error code
785+ integer , intent (in ) :: code
786+ ! > Optional rank-agnostic arguments
787+ class(* ), intent (in ), optional , dimension (..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
788+ a11,a12,a13,a14,a15,a16,a17,a18
789+
790+ state = state_type(STDLIB_FS_ERROR, " code -" , to_string(code)// " ," ,a1,a2,a3,a4,a5,a6,a7,a8, &
791+ a9,a10,a11,a12,a13,a14,a15,a16,a17,a18)
792+ end function FS_ERROR_CODE
793+
794+ pure function FS_ERROR (a1 ,a2 ,a3 ,a4 ,a5 ,a6 ,a7 ,a8 ,a9 ,a10 ,a11 , &
795+ a12 ,a13 ,a14 ,a15 ,a16 ,a17 ,a18 ,a19 ,a20 ) result(state)
796+
797+ type (state_type) :: state
798+ ! > Optional rank-agnostic arguments
799+ class(* ), intent (in ), optional , dimension (..) :: a1,a2,a3,a4,a5,a6,a7,a8,a9,a10, &
800+ a11,a12,a13,a14,a15,a16,a17,a18,a19,a20
801+
802+ state = state_type(STDLIB_FS_ERROR, a1,a2,a3,a4,a5,a6,a7,a8,a9,a10,a11,a12, &
803+ a13,a14,a15,a16,a17,a18,a19,a20)
804+ end function FS_ERROR
805+
773806end module stdlib_system
0 commit comments