@@ -2,8 +2,9 @@ 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, ends_with
66use stdlib_string_type, only: string_type
7+ use stdlib_optval, only: optval
78use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
89implicit none
910private
@@ -115,12 +116,12 @@ module stdlib_system
115116! ! ([Specification](../page/specs/stdlib_system.html#make_directory))
116117! !
117118! ! ### Summary
118- ! ! Creates an empty directory with particular permissions.
119+ ! ! Creates an empty directory with default permissions.
119120! !
120121! ! ### Description
121122! ! This function makes an empty directory according to the path provided.
122- ! ! Relative paths as well as on Windows paths involving either `/` or `\` are accepted
123- ! ! appropriate error message is returned whenever any error occur .
123+ ! ! Relative paths as well as on Windows, paths involving either `/` or `\` are accepted.
124+ ! ! Appropriate error message is returned whenever any error occurs .
124125! !
125126public :: make_directory
126127
@@ -130,12 +131,12 @@ module stdlib_system
130131! ! ([Specification](../page/specs/stdlib_system.html#remove_directory))
131132! !
132133! ! ### Summary
133- ! ! Deletes an empty directory.
134+ ! ! Removes an empty directory.
134135! !
135136! ! ### Description
136- ! ! This function deletes an empty directory according to the path provided.
137+ ! ! This function Removes an empty directory according to the path provided.
137138! ! Relative paths as well as on Windows paths involving either `/` or `\` are accepted.
138- ! ! appropriate error message is returned whenever any error occur .
139+ ! ! Appropriate error message is returned whenever any error occurs .
139140! !
140141public :: remove_directory
141142
@@ -879,6 +880,9 @@ end function stdlib_is_directory
879880
880881end function is_directory
881882
883+ ! A helper function to get the result of the C function `strerror`.
884+ ! `strerror` is a function provided by `<string.h>`.
885+ ! It returns a string describing the meaning of `errno` in the C header `<errno.h>`
882886function c_get_strerror () result(str)
883887 character (len= :), allocatable :: str
884888
@@ -906,40 +910,27 @@ end function strerror
906910end function c_get_strerror
907911
908912! ! makes an empty directory
909- subroutine make_directory (path , mode , err )
913+ subroutine make_directory (path , err )
910914 character (len=* ), intent (in ) :: path
911- integer , intent (in ), optional :: mode
912915 type (state_type), optional , intent (out ) :: err
913916
914917 integer :: code
915918 type (state_type) :: err0
916919
917-
918920 interface
919- integer function stdlib_make_directory (cpath , cmode ) bind(C, name= ' stdlib_make_directory' )
921+ integer function stdlib_make_directory (cpath ) bind(C, name= ' stdlib_make_directory' )
920922 import c_char
921923 character (kind= c_char), intent (in ) :: cpath(* )
922- integer , intent (in ) :: cmode
923924 end function stdlib_make_directory
924925 end interface
925926
926- if (is_windows() .and. present (mode)) then
927- ! _mkdir() doesn't have a `mode` argument
928- err0 = state_type(STDLIB_FS_ERROR, " mode argument not present for Windows" )
927+ code = stdlib_make_directory(to_c_char(trim (path)))
928+
929+ if (code /= 0 ) then
930+ err0 = FS_ERROR_CODE(code, c_get_strerror())
929931 call err0% handle(err)
930- return
931932 end if
932933
933- code = stdlib_make_directory(to_c_char(trim (path)), mode)
934-
935- select case (code)
936- case (0 )
937- return
938- case default
939- ! error
940- err0 = state_type(STDLIB_FS_ERROR, " code:" , to_string(code)// ' ,' , c_get_strerror())
941- call err0% handle(err)
942- end select
943934end subroutine make_directory
944935
945936! ! Removes an empty directory
@@ -959,14 +950,11 @@ end function stdlib_remove_directory
959950
960951 code = stdlib_remove_directory(to_c_char(trim (path)))
961952
962- select case (code)
963- case (0 )
964- return
965- case default
966- ! error
967- err0 = state_type(STDLIB_FS_ERROR, " code:" , to_string(code)// ' ,' , c_get_strerror())
968- call err0% handle(err)
969- end select
953+ if (code /= 0 ) then
954+ err0 = FS_ERROR_CODE(code, c_get_strerror())
955+ call err0% handle(err)
956+ end if
957+
970958end subroutine remove_directory
971959
972960! > Returns the file path of the null device for the current operating system.
0 commit comments