@@ -156,6 +156,32 @@ module stdlib_system
156156! !
157157public :: remove_directory
158158
159+ ! ! version: experimental
160+ ! !
161+ ! ! Gets the current working directory of the process
162+ ! ! ([Specification](../page/specs/stdlib_system.html#get_cwd))
163+ ! !
164+ ! ! ### Summary
165+ ! ! Gets the current working directory.
166+ ! !
167+ ! ! ### Description
168+ ! ! This subroutine gets the current working directory of the process calling this function.
169+ ! !
170+ public :: get_cwd
171+
172+ ! ! version: experimental
173+ ! !
174+ ! ! Sets the current working directory of the process
175+ ! ! ([Specification](../page/specs/stdlib_system.html#set_cwd))
176+ ! !
177+ ! ! ### Summary
178+ ! ! Changes the current working directory to the one specified.
179+ ! !
180+ ! ! ### Description
181+ ! ! This subroutine sets the current working directory of the process calling this function to the one specified.
182+ ! !
183+ public :: set_cwd
184+
159185! ! version: experimental
160186! !
161187! ! Deletes a specified file from the filesystem.
@@ -1024,6 +1050,62 @@ end function stdlib_remove_directory
10241050
10251051end subroutine remove_directory
10261052
1053+ subroutine get_cwd (cwd , err )
1054+ character (:), allocatable , intent (out ) :: cwd
1055+ type (state_type), intent (out ) :: err
1056+ type (state_type) :: err0
1057+
1058+ interface
1059+ type (c_ptr) function stdlib_get_cwd(len, stat) bind(C, name= ' stdlib_get_cwd' )
1060+ import c_ptr, c_size_t
1061+ integer (c_size_t), intent (out ) :: len
1062+ integer :: stat
1063+ end function stdlib_get_cwd
1064+ end interface
1065+
1066+ type (c_ptr) :: c_str_ptr
1067+ integer (c_size_t) :: len, i
1068+ integer :: stat
1069+ character (kind= c_char), pointer :: c_str(:)
1070+
1071+ c_str_ptr = stdlib_get_cwd(len, stat)
1072+
1073+ if (stat /= 0 ) then
1074+ err0 = state_type(STDLIB_FS_ERROR, " code: " , to_string(stat)// " ," , c_get_strerror())
1075+ call err0% handle(err)
1076+ end if
1077+
1078+ call c_f_pointer(c_str_ptr, c_str, [len])
1079+
1080+ allocate (character (len= len) :: cwd)
1081+
1082+ do concurrent (i= 1 :len)
1083+ cwd(i:i) = c_str(i)
1084+ end do
1085+ end subroutine get_cwd
1086+
1087+ subroutine set_cwd (path , err )
1088+ character (len=* ), intent (in ) :: path
1089+ type (state_type), intent (out ) :: err
1090+ type (state_type) :: err0
1091+
1092+ interface
1093+ integer function stdlib_set_cwd (path ) bind(C, name= ' stdlib_set_cwd' )
1094+ import c_char
1095+ character (kind= c_char), intent (in ) :: path(* )
1096+ end function stdlib_set_cwd
1097+ end interface
1098+
1099+ integer :: code
1100+
1101+ code = stdlib_set_cwd(to_c_char(trim (path)))
1102+
1103+ if (code /= 0 ) then
1104+ err0 = state_type(STDLIB_FS_ERROR, " code: " , to_string(code)// " ," , c_get_strerror())
1105+ call err0% handle(err)
1106+ end if
1107+ end subroutine set_cwd
1108+
10271109! > Returns the file path of the null device for the current operating system.
10281110! >
10291111! > Version: Helper function.
0 commit comments