@@ -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, ends_with
5+ use stdlib_strings, only: to_c_char, find
66use stdlib_string_type, only: string_type
77use stdlib_optval, only: optval
88use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
@@ -125,6 +125,22 @@ module stdlib_system
125125! !
126126public :: make_directory
127127
128+ ! ! version: experimental
129+ ! !
130+ ! ! Makes an empty directory, also creating all the parent directories required.
131+ ! ! ([Specification](../page/specs/stdlib_system.html#make_directory))
132+ ! !
133+ ! ! ### Summary
134+ ! ! Creates an empty directory with all the parent directories required to do so.
135+ ! !
136+ ! ! ### Description
137+ ! ! This function makes an empty directory according to the path provided.
138+ ! ! It also creates all the parent directories required in doing so.
139+ ! ! Relative paths as well as on Windows, paths involving either `/` or `\` are accepted.
140+ ! ! Appropriate error message is returned whenever any error occurs.
141+ ! !
142+ public :: make_directory_all
143+
128144! ! version: experimental
129145! !
130146! ! Removes an empty directory.
@@ -933,6 +949,51 @@ end function stdlib_make_directory
933949
934950end subroutine make_directory
935951
952+ subroutine make_directory_all (path , err )
953+ character (len=* ), intent (in ) :: path
954+ type (state_type), optional , intent (out ) :: err
955+
956+ integer :: code, i, indx
957+ type (state_type) :: err0
958+ character (len= 1 ) :: sep
959+ logical :: is_dir
960+
961+ sep = path_sep()
962+ i = 1
963+ indx = find(path, sep, i)
964+
965+ do
966+ ! Base case to exit the loop
967+ if (indx == 0 .or. indx == len (trim (path))) then
968+ is_dir = is_directory(path)
969+
970+ if (.not. is_dir) then
971+ call make_directory(path, err0)
972+
973+ if (err0% error()) then
974+ call err0% handle(err)
975+ end if
976+
977+ return
978+ end if
979+ end if
980+
981+ is_dir = is_directory(path(1 :indx))
982+
983+ if (.not. is_dir) then
984+ call make_directory(path(1 :indx), err0)
985+
986+ if (err0% error()) then
987+ call err0% handle(err)
988+ return
989+ end if
990+ end if
991+
992+ i = i + 1
993+ indx = find(path, sep, i)
994+ end do
995+ end subroutine make_directory_all
996+
936997! ! Removes an empty directory
937998subroutine remove_directory (path , err )
938999 character (len=* ), intent (in ) :: path
0 commit comments