Skip to content

Commit def840d

Browse files
authored
system: delete_file (#966)
2 parents 60d0a76 + 53ffe5a commit def840d

File tree

6 files changed

+215
-13
lines changed

6 files changed

+215
-13
lines changed

doc/specs/stdlib_io.md

+1
Original file line numberDiff line numberDiff line change
@@ -304,3 +304,4 @@ Exceptions trigger an `error stop` unless the optional `err` argument is provide
304304
```fortran
305305
{!example/io/example_get_file.f90!}
306306
```
307+

doc/specs/stdlib_system.md

+49-9
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ Additionally, a callback function can be specified to execute upon process compl
2424

2525
### Syntax
2626

27-
`process = ` [[stdlib_subprocess(module):run(interface)]] `(args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])`
27+
`process = ` [[stdlib_system(module):run(interface)]] `(args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])`
2828

2929
### Arguments
3030

@@ -69,7 +69,7 @@ Additionally, a callback function can be specified to execute upon process compl
6969

7070
### Syntax
7171

72-
`process = ` [[stdlib_subprocess(module):runasync(interface)]] `(args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])`
72+
`process = ` [[stdlib_system(module):runasync(interface)]] `(args [, stdin] [, want_stdout] [, want_stderr] [, callback] [, payload])`
7373

7474
### Arguments
7575

@@ -108,7 +108,7 @@ This is useful for monitoring the status of asynchronous processes created with
108108

109109
### Syntax
110110

111-
`status = ` [[stdlib_subprocess(module):is_running(interface)]] `(process)`
111+
`status = ` [[stdlib_system(module):is_running(interface)]] `(process)`
112112

113113
### Arguments
114114

@@ -139,7 +139,7 @@ This is useful for determining whether asynchronous processes created with the `
139139

140140
### Syntax
141141

142-
`status = ` [[stdlib_subprocess(module):is_completed(interface)]] `(process)`
142+
`status = ` [[stdlib_system(module):is_completed(interface)]] `(process)`
143143

144144
### Arguments
145145

@@ -174,7 +174,7 @@ The result is a real value representing the elapsed time in seconds, measured fr
174174

175175
### Syntax
176176

177-
`delta_t = ` [[stdlib_subprocess(module):elapsed(subroutine)]] `(process)`
177+
`delta_t = ` [[stdlib_system(module):elapsed(subroutine)]] `(process)`
178178

179179
### Arguments
180180

@@ -212,7 +212,7 @@ in case of process hang or delay.
212212

213213
### Syntax
214214

215-
`call ` [[stdlib_subprocess(module):wait(subroutine)]] `(process [, max_wait_time])`
215+
`call ` [[stdlib_system(module):wait(subroutine)]] `(process [, max_wait_time])`
216216

217217
### Arguments
218218

@@ -243,7 +243,7 @@ This is especially useful for monitoring asynchronous processes and retrieving t
243243

244244
### Syntax
245245

246-
`call ` [[stdlib_subprocess(module):update(subroutine)]] `(process)`
246+
`call ` [[stdlib_system(module):update(subroutine)]] `(process)`
247247

248248
### Arguments
249249

@@ -269,7 +269,7 @@ This interface is useful when a process needs to be forcefully stopped, for exam
269269

270270
### Syntax
271271

272-
`call ` [[stdlib_subprocess(module):kill(subroutine)]] `(process, success)`
272+
`call ` [[stdlib_system(module):kill(subroutine)]] `(process, success)`
273273

274274
### Arguments
275275

@@ -431,7 +431,7 @@ It is designed to work across multiple platforms. On Windows, paths with both fo
431431

432432
### Syntax
433433

434-
`result = [[stdlib_io(module):is_directory(function)]] (path)`
434+
`result = [[stdlib_system(module):is_directory(function)]] (path)`
435435

436436
### Class
437437

@@ -492,3 +492,43 @@ None.
492492
{!example/system/example_null_device.f90!}
493493
```
494494

495+
## `delete_file` - Delete a file
496+
497+
### Status
498+
499+
Experimental
500+
501+
### Description
502+
503+
This subroutine deletes a specified file from the filesystem. It ensures that the file exists and is not a directory before attempting deletion.
504+
If the file cannot be deleted due to permissions, being a directory, or other issues, an error is raised.
505+
The function provides an optional error-handling mechanism via the `state_type` class. If the `err` argument is not provided, exceptions will trigger an `error stop`.
506+
507+
### Syntax
508+
509+
`call [[stdlib_system(module):delete_file(subroutine)]] (path [, err])`
510+
511+
### Class
512+
Subroutine
513+
514+
### Arguments
515+
516+
`path`: Shall be a character string containing the path to the file to be deleted. It is an `intent(in)` argument.
517+
518+
`err` (optional): Shall be a `type(state_type)` variable for error handling. If provided, errors are returned as a state object. If not provided, the program stops execution on error.
519+
520+
### Behavior
521+
522+
- Checks if the file exists. If not, an error is raised.
523+
- Ensures the path is not a directory before deletion.
524+
- Attempts to delete the file, raising an error if unsuccessful.
525+
526+
### Return values
527+
528+
The file is removed from the filesystem if the operation is successful. If the operation fails, an error is raised.
529+
530+
### Example
531+
532+
```fortran
533+
{!example/system/example_delete_file.f90!}
534+
```

example/system/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
ADD_EXAMPLE(get_runtime_os)
2+
ADD_EXAMPLE(delete_file)
23
ADD_EXAMPLE(is_directory)
34
ADD_EXAMPLE(null_device)
45
ADD_EXAMPLE(os_type)
+18
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
! Demonstrate usage of `delete_file`
2+
program example_delete_file
3+
use stdlib_system, only: delete_file
4+
use stdlib_error, only: state_type
5+
implicit none
6+
7+
type(state_type) :: err
8+
character(*), parameter :: filename = "example.txt"
9+
10+
! Delete a file with error handling
11+
call delete_file(filename, err)
12+
13+
if (err%error()) then
14+
print *, err%print()
15+
else
16+
print *, "File "//filename//" deleted successfully."
17+
end if
18+
end program example_delete_file

src/stdlib_system.F90

+65-2
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module stdlib_system
33
c_f_pointer
44
use stdlib_kinds, only: int64, dp, c_bool, c_char
55
use stdlib_strings, only: to_c_char
6+
use stdlib_error, only: state_type, STDLIB_SUCCESS, STDLIB_FS_ERROR
67
implicit none
78
private
89
public :: sleep
@@ -86,7 +87,7 @@ module stdlib_system
8687
!! version: experimental
8788
!!
8889
!! Tests if a given path matches an existing directory.
89-
!! ([Specification](../page/specs/stdlib_io.html#is_directory-test-if-a-path-is-a-directory))
90+
!! ([Specification](../page/specs/stdlib_system.html#is_directory-test-if-a-path-is-a-directory))
9091
!!
9192
!!### Summary
9293
!! Function to evaluate whether a specified path corresponds to an existing directory.
@@ -98,7 +99,24 @@ module stdlib_system
9899
!! Windows, and various UNIX-like environments. On unsupported operating systems, the function will return `.false.`.
99100
!!
100101
public :: is_directory
101-
102+
103+
!! version: experimental
104+
!!
105+
!! Deletes a specified file from the filesystem.
106+
!! ([Specification](../page/specs/stdlib_system.html#delete_file-delete-a-file))
107+
!!
108+
!!### Summary
109+
!! Subroutine to safely delete a file from the filesystem. It handles errors gracefully using the library's `state_type`.
110+
!!
111+
!!### Description
112+
!!
113+
!! This subroutine deletes a specified file. If the file is a directory or inaccessible, an error is raised.
114+
!! If the file does not exist, a warning is returned, but no error state. Errors are handled using the
115+
!! library's `state_type` mechanism. If the optional `err` argument is not provided, exceptions trigger
116+
!! an `error stop`.
117+
!!
118+
public :: delete_file
119+
102120
!! version: experimental
103121
!!
104122
!! Returns the file path of the null device, which discards all data written to it.
@@ -707,4 +725,49 @@ end function process_null_device
707725

708726
end function null_device
709727

728+
!> Delete a file at the given path.
729+
subroutine delete_file(path, err)
730+
character(*), intent(in) :: path
731+
type(state_type), optional, intent(out) :: err
732+
733+
!> Local variables
734+
integer :: file_unit, ios
735+
type(state_type) :: err0
736+
character(len=512) :: msg
737+
logical :: file_exists
738+
739+
! Verify the file is not a directory.
740+
if (is_directory(path)) then
741+
! If unable to open, assume it's a directory or inaccessible
742+
err0 = state_type(STDLIB_FS_ERROR,'Cannot delete',path,'- is a directory')
743+
call err0%handle(err)
744+
return
745+
end if
746+
747+
! Check if the path exists
748+
! Because Intel compilers return .false. if path is a directory, this must be tested
749+
! _after_ the directory test
750+
inquire(file=path, exist=file_exists)
751+
if (.not. file_exists) then
752+
! File does not exist, return non-error status
753+
err0 = state_type(STDLIB_SUCCESS,path,' not deleted: file does not exist')
754+
call err0%handle(err)
755+
return
756+
endif
757+
758+
! Close and delete the file
759+
open(newunit=file_unit, file=path, status='old', iostat=ios, iomsg=msg)
760+
if (ios /= 0) then
761+
err0 = state_type(STDLIB_FS_ERROR,'Cannot delete',path,'-',msg)
762+
call err0%handle(err)
763+
return
764+
end if
765+
close(unit=file_unit, status='delete', iostat=ios, iomsg=msg)
766+
if (ios /= 0) then
767+
err0 = state_type(STDLIB_FS_ERROR,'Cannot delete',path,'-',msg)
768+
call err0%handle(err)
769+
return
770+
end if
771+
end subroutine delete_file
772+
710773
end module stdlib_system

test/system/test_filesystem.f90

+81-2
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
module test_filesystem
22
use testdrive, only : new_unittest, unittest_type, error_type, check, skip_test
3-
use stdlib_system, only: is_directory
3+
use stdlib_system, only: is_directory, delete_file
4+
use stdlib_error, only: state_type
45

56
implicit none
67

@@ -13,7 +14,10 @@ subroutine collect_suite(testsuite)
1314

1415
testsuite = [ &
1516
new_unittest("fs_is_directory_dir", test_is_directory_dir), &
16-
new_unittest("fs_is_directory_file", test_is_directory_file) &
17+
new_unittest("fs_is_directory_file", test_is_directory_file), &
18+
new_unittest("fs_delete_non_existent", test_delete_file_non_existent), &
19+
new_unittest("fs_delete_existing_file", test_delete_file_existing), &
20+
new_unittest("fs_delete_file_being_dir", test_delete_directory) &
1721
]
1822
end subroutine collect_suite
1923

@@ -67,6 +71,81 @@ subroutine test_is_directory_file(error)
6771

6872
end subroutine test_is_directory_file
6973

74+
subroutine test_delete_file_non_existent(error)
75+
!> Error handling
76+
type(error_type), allocatable, intent(out) :: error
77+
type(state_type) :: state
78+
79+
! Attempt to delete a file that doesn't exist
80+
call delete_file('non_existent_file.txt', state)
81+
82+
call check(error, state%ok(), 'Error should not be triggered for non-existent file')
83+
if (allocated(error)) return
84+
85+
end subroutine test_delete_file_non_existent
86+
87+
subroutine test_delete_file_existing(error)
88+
!> Error handling
89+
type(error_type), allocatable, intent(out) :: error
90+
91+
character(len=256) :: filename
92+
type(state_type) :: state
93+
integer :: ios,iunit
94+
logical :: is_present
95+
character(len=512) :: msg
96+
97+
filename = 'existing_file.txt'
98+
99+
! Create a file to be deleted
100+
open(newunit=iunit, file=filename, status='replace', iostat=ios, iomsg=msg)
101+
call check(error, ios==0, 'Failed to create test file')
102+
if (allocated(error)) return
103+
close(iunit)
104+
105+
! Attempt to delete the existing file
106+
call delete_file(filename, state)
107+
108+
! Check deletion successful
109+
call check(error, state%ok(), 'delete_file returned '//state%print())
110+
if (allocated(error)) return
111+
112+
! Check if the file was successfully deleted (should no longer exist)
113+
inquire(file=filename, exist=is_present)
114+
115+
call check(error, .not.is_present, 'File still present after delete')
116+
if (allocated(error)) return
117+
118+
end subroutine test_delete_file_existing
119+
120+
subroutine test_delete_directory(error)
121+
!> Error handling
122+
type(error_type), allocatable, intent(out) :: error
123+
character(len=256) :: filename
124+
type(state_type) :: state
125+
integer :: ios,iocmd
126+
character(len=512) :: msg
127+
128+
filename = 'test_directory'
129+
130+
! The directory is not nested: it should be cross-platform to just call `mkdir`
131+
call execute_command_line('mkdir ' // filename, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
132+
call check(error, ios==0 .and. iocmd==0, 'Cannot init delete_directory test: '//trim(msg))
133+
if (allocated(error)) return
134+
135+
! Attempt to delete a directory (which should fail)
136+
call delete_file(filename, state)
137+
138+
! Check that an error was raised since the target is a directory
139+
call check(error, state%error(), 'Error was not triggered trying to delete directory')
140+
if (allocated(error)) return
141+
142+
! Clean up: remove the empty directory
143+
call execute_command_line('rmdir ' // filename, exitstat=ios, cmdstat=iocmd, cmdmsg=msg)
144+
call check(error, ios==0 .and. iocmd==0, 'Cannot cleanup delete_directory test: '//trim(msg))
145+
if (allocated(error)) return
146+
147+
end subroutine test_delete_directory
148+
70149

71150
end module test_filesystem
72151

0 commit comments

Comments
 (0)