Skip to content

Commit eeeb634

Browse files
committed
Add mkdir subroutine
1 parent 21739b7 commit eeeb634

File tree

2 files changed

+54
-38
lines changed

2 files changed

+54
-38
lines changed

src/stdlib_io_filesystem.F90

Lines changed: 20 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module stdlib_io_filesystem
66
implicit none
77
private
88

9-
public :: temp_dir, is_windows, exists, list_dir, rm_dir, run
9+
public :: temp_dir, is_windows, exists, list_dir, mkdir, rmdir, run
1010

1111
character(*), parameter :: temp_dir = 'temp'
1212
character(*), parameter :: listed_contents = temp_dir//'/listed_contents.txt'
@@ -69,7 +69,7 @@ subroutine list_dir(dir, files, iostat, iomsg)
6969
stat = 0
7070

7171
if (.not. exists(temp_dir)) then
72-
call run('mkdir '//temp_dir, stat)
72+
call mkdir(temp_dir, stat)
7373
if (stat /= 0) then
7474
if (present(iostat)) iostat = stat
7575
if (present(iomsg)) iomsg = "Failed to create temporary directory '"//temp_dir//"'."
@@ -104,11 +104,27 @@ subroutine list_dir(dir, files, iostat, iomsg)
104104
close(unit, status="delete")
105105
end
106106

107+
!> Version: experimental
108+
!>
109+
!> Create a directory.
110+
!> [Specification](../page/specs/stdlib_io.html#mkdir)
111+
subroutine mkdir(dir, iostat, iomsg)
112+
character(len=*), intent(in) :: dir
113+
integer, optional, intent(out) :: iostat
114+
character(len=:), allocatable, optional, intent(out) :: iomsg
115+
116+
if (is_windows()) then
117+
call run('mkdir '//dir, iostat, iomsg)
118+
else
119+
call run('mkdir -p '//dir, iostat, iomsg)
120+
end if
121+
end
122+
107123
!> Version: experimental
108124
!>
109125
!> Remove a directory including its contents.
110-
!> [Specification](../page/specs/stdlib_io.html#rm_dir)
111-
subroutine rm_dir(dir)
126+
!> [Specification](../page/specs/stdlib_io.html#rmdir)
127+
subroutine rmdir(dir)
112128
character(len=*), intent(in) :: dir
113129

114130
if (is_windows()) then

test/io/test_filesystem.f90

Lines changed: 34 additions & 34 deletions
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,8 @@ subroutine collect_filesystem(testsuite)
2828
new_unittest("fs_list_dir_one_file", fs_list_dir_one_file), &
2929
new_unittest("fs_list_dir_two_files", fs_list_dir_two_files), &
3030
new_unittest("fs_list_dir_one_file_one_dir", fs_list_dir_one_file_one_dir), &
31-
new_unittest("fs_rm_dir_empty", fs_rm_dir_empty), &
32-
new_unittest("fs_rm_dir_with_contents", fs_rm_dir_with_contents) &
31+
new_unittest("fs_rmdir_empty", fs_rmdir_empty), &
32+
new_unittest("fs_rmdir_with_contents", fs_rmdir_with_contents) &
3333
]
3434
end
3535

@@ -113,8 +113,8 @@ subroutine fs_list_dir_empty(error)
113113
integer :: stat
114114
type(string_type), allocatable :: files(:)
115115

116-
call rm_dir(temp_list_dir)
117-
call run('mkdir '//temp_list_dir, iostat=stat)
116+
call rmdir(temp_list_dir)
117+
call mkdir(temp_list_dir, stat)
118118
if (stat /= 0) then
119119
call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return
120120
end if
@@ -123,7 +123,7 @@ subroutine fs_list_dir_empty(error)
123123
call check(error, stat, "Listing the contents of an empty directory shouldn't fail.")
124124
call check(error, size(files) == 0, "The directory should be empty.")
125125

126-
call rm_dir(temp_list_dir)
126+
call rmdir(temp_list_dir)
127127
end
128128

129129
subroutine fs_list_dir_one_file(error)
@@ -134,8 +134,8 @@ subroutine fs_list_dir_one_file(error)
134134
type(string_type), allocatable :: files(:)
135135
character(*), parameter :: filename = 'abc.txt'
136136

137-
call rm_dir(temp_list_dir)
138-
call run('mkdir '//temp_list_dir, iostat=stat)
137+
call rmdir(temp_list_dir)
138+
call mkdir(temp_list_dir, stat)
139139
if (stat /= 0) then
140140
call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return
141141
end if
@@ -150,7 +150,7 @@ subroutine fs_list_dir_one_file(error)
150150
call check(error, size(files) == 1, "The directory should contain one file.")
151151
call check(error, char(files(1)) == filename, "The file should be '"//filename//"'.")
152152

153-
call rm_dir(temp_list_dir)
153+
call rmdir(temp_list_dir)
154154
end
155155

156156
subroutine fs_list_dir_two_files(error)
@@ -162,8 +162,8 @@ subroutine fs_list_dir_two_files(error)
162162
character(*), parameter :: filename1 = 'abc.txt'
163163
character(*), parameter :: filename2 = 'xyz'
164164

165-
call rm_dir(temp_list_dir)
166-
call run('mkdir '//temp_list_dir, iostat=stat)
165+
call rmdir(temp_list_dir)
166+
call mkdir(temp_list_dir, stat)
167167
if (stat /= 0) then
168168
call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return
169169
end if
@@ -184,7 +184,7 @@ subroutine fs_list_dir_two_files(error)
184184
call check(error, char(files(1)) == filename1, "The file should be '"//filename1//"'.")
185185
call check(error, char(files(2)) == filename2, "The file should be '"//filename2//"'.")
186186

187-
call rm_dir(temp_list_dir)
187+
call rmdir(temp_list_dir)
188188
end
189189

190190
subroutine fs_list_dir_one_file_one_dir(error)
@@ -196,8 +196,8 @@ subroutine fs_list_dir_one_file_one_dir(error)
196196
character(*), parameter :: filename1 = 'abc.txt'
197197
character(*), parameter :: dir = 'xyz'
198198

199-
call rm_dir(temp_list_dir)
200-
call run('mkdir '//temp_list_dir, iostat=stat)
199+
call rmdir(temp_list_dir)
200+
call mkdir(temp_list_dir, stat)
201201
if (stat /= 0) then
202202
call test_failed(error, "Creating directory '"//temp_list_dir//"' failed."); return
203203
end if
@@ -208,9 +208,9 @@ subroutine fs_list_dir_one_file_one_dir(error)
208208
end if
209209

210210
if (is_windows()) then
211-
call run('mkdir '//temp_list_dir//'\'//dir, iostat=stat)
211+
call mkdir(temp_list_dir//'\'//dir, stat)
212212
else
213-
call run('mkdir '//temp_list_dir//'/'//dir, iostat=stat)
213+
call mkdir(temp_list_dir//'/'//dir, stat)
214214
end if
215215
if (stat /= 0) then
216216
call test_failed(error, "Creating dir in directory '"//temp_list_dir//"' failed."); return
@@ -222,38 +222,38 @@ subroutine fs_list_dir_one_file_one_dir(error)
222222
call check(error, char(contents(1)) == filename1, "The file should be '"//filename1//"'.")
223223
call check(error, char(contents(2)) == dir, "The file should be '"//dir//"'.")
224224

225-
call rm_dir(temp_list_dir)
225+
call rmdir(temp_list_dir)
226226
end
227227

228-
subroutine fs_rm_dir_empty(error)
228+
subroutine fs_rmdir_empty(error)
229229
type(error_type), allocatable, intent(out) :: error
230230

231-
character(*), parameter :: filename = "empty_dir_to_remove"
231+
character(*), parameter :: dir = "empty_dir_to_remove"
232232

233-
call rm_dir(filename)
234-
call check(error, .not. exists(filename), "Directory should not exist.")
235-
call run('mkdir '//filename)
236-
call check(error, exists(filename), "Directory should exist.")
237-
call rm_dir(filename)
238-
call check(error, .not. exists(filename), "Directory should not exist.")
233+
call rmdir(dir)
234+
call check(error, .not. exists(dir), "Directory should not exist.")
235+
call mkdir(dir)
236+
call check(error, exists(dir), "Directory should exist.")
237+
call rmdir(dir)
238+
call check(error, .not. exists(dir), "Directory should not exist.")
239239
end
240240

241-
subroutine fs_rm_dir_with_contents(error)
241+
subroutine fs_rmdir_with_contents(error)
242242
type(error_type), allocatable, intent(out) :: error
243243

244-
character(*), parameter :: filename = "dir_with_contents_to_remove"
244+
character(*), parameter :: dir = "dir_with_contents_to_remove"
245245

246-
call rm_dir(filename)
247-
call check(error, .not. exists(filename), "Directory should not exist.")
248-
call run('mkdir '//filename)
249-
call check(error, exists(filename), "Directory should exist.")
246+
call rmdir(dir)
247+
call check(error, .not. exists(dir), "Directory should not exist.")
248+
call mkdir(dir)
249+
call check(error, exists(dir), "Directory should exist.")
250250
if (is_windows()) then
251-
call run('mkdir '//filename//'\'//'another_dir')
251+
call mkdir(dir//'\'//'another_dir')
252252
else
253-
call run('mkdir '//filename//'/'//'another_dir')
253+
call mkdir(dir//'/'//'another_dir')
254254
end if
255-
call rm_dir(filename)
256-
call check(error, .not. exists(filename), "Directory should not exist.")
255+
call rmdir(dir)
256+
call check(error, .not. exists(dir), "Directory should not exist.")
257257
end
258258

259259
subroutine delete_file(filename)

0 commit comments

Comments
 (0)