Skip to content

Commit 7b76756

Browse files
committed
Add documentation
1 parent 6aa19aa commit 7b76756

File tree

4 files changed

+212
-25
lines changed

4 files changed

+212
-25
lines changed

doc/specs/stdlib_array.md

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -147,7 +147,7 @@ Add an array of defined type and rank to a list of array wrappers.
147147

148148
#### Syntax
149149

150-
`call ` [[stdlib_array(module):add_array(interface)]] ` (arrays, array[, stat, msg, name])`
150+
`call ` [[stdlib_array(module):add_array(interface)]] `(arrays, array[, stat, msg, name])`
151151

152152
#### Class
153153

@@ -170,6 +170,7 @@ Pure subroutine.
170170
```fortran
171171
{!example/io/example_save_npz.f90!}
172172
```
173+
173174
### `get_values`
174175

175176
#### Status
@@ -182,7 +183,7 @@ Get the values of the array within the array wrapper.
182183

183184
#### Syntax
184185

185-
`call ` [[stdlib_array(module):array_wrapper_type(type)]] `%` [[array_wrapper_type(type):get_values(bound)]] ` (wrapper, values[, stat, msg])`
186+
`call ` [[stdlib_array(module):array_wrapper_type(type)]] `%` [[array_wrapper_type(type):get_values(bound)]] `(wrapper, values[, stat, msg])`
186187

187188
#### Class
188189

doc/specs/stdlib_io.md

Lines changed: 181 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -136,11 +136,11 @@ Loads an `array` from a npy formatted binary file.
136136

137137
### Syntax
138138

139-
`call ` [[stdlib_io_npy(module):load_npy(interface)]] `(filename, array[, iostat][, iomsg])`
139+
`call ` [[stdlib_io_np(module):load_npy(interface)]] `(filename, array[, iostat][, iomsg])`
140140

141141
### Arguments
142142

143-
`filename`: Shall be a character expression containing the file name from which to load the `array`.
143+
`filename`: Shall be a character expression containing the file name from which to load the `array`.
144144
This argument is `intent(in)`.
145145

146146
`array`: Shall be an allocatable array of any rank of type `real`, `complex` or `integer`.
@@ -164,7 +164,6 @@ Returns an allocated `array` with the content of `filename` in case of success.
164164
{!example/io/example_loadnpy.f90!}
165165
```
166166

167-
168167
## `save_npy`
169168

170169
### Status
@@ -177,7 +176,7 @@ Saves an `array` into a npy formatted binary file.
177176

178177
### Syntax
179178

180-
`call ` [[stdlib_io_npy(module):save_npy(interface)]] `(filename, array[, iostat][, iomsg])`
179+
`call ` [[stdlib_io_np(module):save_npy(interface)]] `(filename, array[, iostat][, iomsg])`
181180

182181
### Arguments
183182

@@ -205,6 +204,70 @@ Provides a npy file called `filename` that contains the rank-2 `array`.
205204
{!example/io/example_savenpy.f90!}
206205
```
207206

207+
## `load_npz`
208+
209+
### Status
210+
211+
Experimental
212+
213+
### Description
214+
215+
Populates an array of `array_wrapper_type` with the contents of an npz file.
216+
217+
### Syntax
218+
219+
`call ` [[stdlib_io_np(module):load_npz(interface)]] `(filename, arrays[, iostat][, iomsg][, tmp_dir])`
220+
221+
### Arguments
222+
223+
`filename`: Shall be a character expression containing the name of the npz file to load from. The argument is `intent(in)`.
224+
225+
`arrays`: Shall be an allocatable array of type `array_wrapper_type` to load the content of the npz file to. This argument is `intent(out)`.
226+
227+
`iostat`: Default integer, contains status of loading to file, zero in case of success. This argument is `optional` and `intent(out)`.
228+
229+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an optional argument, error message will be dropped if not present. This argument is `intent(out)`.
230+
231+
`tmp_dir`: Shall be a character expression containing the name of the temporary directory to extract the npz file to. The argument is `optional` and `intent(in)`.
232+
233+
### Example
234+
235+
```fortran
236+
{!example/io/example_load_npz.f90!}
237+
```
238+
239+
## `save_npz`
240+
241+
### Status
242+
243+
Experimental
244+
245+
### Description
246+
247+
Saves an array of `array_wrapper_type` into a npz file.
248+
249+
### Syntax
250+
251+
`call ` [[stdlib_io_np(module):save_npz(interface)]] `(filename, arrays[, iostat][, iomsg][, compressed])`
252+
253+
### Arguments
254+
255+
`filename`: Shall be a character expression containing the name of the file that contains the arrays. This argument is `intent(in)`.
256+
257+
`arrays`: Shall be arrays of type `array_wrapper_type` that are meant to be saved to disk. This argument is `intent(in)`.
258+
259+
`iostat`: Default integer, contains status of saving to file, zero in case of success. This argument is `optional` and `intent(out)`.
260+
261+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an optional argument, error message will be dropped if not present. This argument is `intent(out)`.
262+
263+
`compressed`: Shall be a logical expression that determines if the npz file should be compressed. The argument is `optional` and `intent(in)`. The default value is `.false.`.
264+
265+
### Example
266+
267+
```fortran
268+
{!example/io/example_save_npz.f90!}
269+
```
270+
208271
## `getline`
209272

210273
### Status
@@ -260,3 +323,117 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module.
260323
```fortran
261324
{!example/io/example_fmt_constants.f90!}
262325
```
326+
327+
## `zip`
328+
329+
### Status
330+
331+
Experimental
332+
333+
### Description
334+
335+
Compresses a file or directory into a zip archive.
336+
337+
### Syntax
338+
339+
`call ` [[stdlib_io_zip(module):zip(subroutine)]] ` (output_file, files[, stat][, msg][, compressed])`
340+
341+
### Arguments
342+
343+
`output_file`: Character expression representing the name of the zip file to create. This argument is `intent(in)`.
344+
345+
`files`: Array of `string_type` representing the names of the files to compress. This argument is `intent(in)`.
346+
347+
`stat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.
348+
349+
`msg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an `optional` argument, error message will be dropped if not present. This argument is `intent(out)`.
350+
351+
`compressed`: Logical expression that determines if the zip file should be compressed. The argument is `optional` and `intent(in)`. The default value is `.true.`.
352+
353+
## `unzip`
354+
355+
### Status
356+
357+
Experimental
358+
359+
### Description
360+
361+
Extracts a zip archive into a directory.
362+
363+
### Syntax
364+
365+
`call ` [[stdlib_io_zip(module):unzip(subroutine)]] ` (filename, outputdir[, stat][, msg])`
366+
367+
### Arguments
368+
369+
`filename`: Character expression representing the name of the zip file to extract. This argument is `intent(in)`.
370+
371+
`outputdir`: Character expression representing the name of the directory to extract the zip file to. This argument is `intent(in)`.
372+
373+
`stat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.
374+
375+
`msg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an `optional` argument, error message will be dropped if not present. This argument is `intent(out)`.
376+
377+
## `exists`
378+
379+
### Status
380+
381+
Experimental
382+
383+
### Description
384+
385+
Whether a file or directory exists at the given location in the filesystem.
386+
387+
### Syntax
388+
389+
`is_existing = ` [[stdlib_io_filesystem(module):exists(function)]] ` (filename)`
390+
391+
### Arguments
392+
393+
`filename`: Character expression representing the name of the file or directory to check for existence. This argument is `intent(in)`.
394+
395+
## `list_dir`
396+
397+
### Status
398+
399+
Experimental
400+
401+
### Description
402+
403+
Lists the contents of a directory.
404+
405+
### Syntax
406+
407+
`call ` [[stdlib_io_filesystem(module):list_dir(subroutine)]] ` (dir, files[, iostat][, iomsg])`
408+
409+
### Arguments
410+
411+
`dir`: Character expression representing the name of the directory to list. This argument is `intent(in)`.
412+
413+
`files`: Array of `string_type` representing the names of the files in the directory. This argument is `intent(out)`.
414+
415+
`iostat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.
416+
417+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an `optional` argument, error message will be dropped if not present. This argument is `intent(out)`.
418+
419+
## `run`
420+
421+
### Status
422+
423+
Experimental
424+
425+
### Description
426+
427+
Runs a command in the shell.
428+
429+
### Syntax
430+
431+
`call ` [[stdlib_io_filesystem(module):run(subroutine)]] ` (command[, iostat][, iomsg])`
432+
433+
### Arguments
434+
435+
`command`: Character expression representing the command to run. This argument is `intent(in)`.
436+
437+
`iostat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.
438+
439+
`iomsg`: Deferred length character value, contains error message in case `iostat` is non-zero. It is an `optional` argument, error message will be dropped if not present. This argument is `intent(out)`.

src/stdlib_io_filesystem.f90

Lines changed: 26 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ module stdlib_io_filesystem
1616
!> Version: experimental
1717
!>
1818
!> Whether a file or directory exists at the given path.
19+
!> [Specification](../page/specs/stdlib_io.html#exists)
1920
logical function exists(filename)
2021
!> Name of the file or directory.
2122
character(len=*), intent(in) :: filename
@@ -30,44 +31,49 @@ logical function exists(filename)
3031
!> Version: experimental
3132
!>
3233
!> List files and directories of a directory. Does not list hidden files.
33-
subroutine list_dir(dir, files, stat, msg)
34+
!> [Specification](../page/specs/stdlib_io.html#list_dir)
35+
subroutine list_dir(dir, files, iostat, iomsg)
3436
!> Directory to list.
3537
character(len=*), intent(in) :: dir
3638
!> List of files and directories.
3739
type(string_type), allocatable, intent(out) :: files(:)
3840
!> Status of listing.
39-
integer, intent(out) :: stat
41+
integer, optional, intent(out) :: iostat
4042
!> Error message.
41-
character(len=:), allocatable, optional, intent(out) :: msg
43+
character(len=:), allocatable, optional, intent(out) :: iomsg
4244

43-
integer :: unit, iostat
45+
integer :: unit, stat
4446
character(len=256) :: line
4547

4648
stat = 0
4749

4850
if (.not. exists(temp_dir)) then
4951
call run('mkdir '//temp_dir, stat)
5052
if (stat /= 0) then
51-
if (present(msg)) msg = "Failed to create temporary directory '"//temp_dir//"'."; return
53+
if (present(iostat)) iostat = stat
54+
if (present(iomsg)) iomsg = "Failed to create temporary directory '"//temp_dir//"'."
55+
return
5256
end if
5357
end if
5458

5559
call run('ls '//dir//' > '//listed_contents, stat)
5660
if (stat /= 0) then
57-
if (present(msg)) then
58-
msg = "Failed to list files in directory '"//dir//"'."; return
59-
end if
61+
if (present(iostat)) iostat = stat
62+
if (present(iomsg)) iomsg = "Failed to list files in directory '"//dir//"'."
63+
return
6064
end if
6165

6266
open(newunit=unit, file=listed_contents, status='old', action='read', iostat=stat)
6367
if (stat /= 0) then
64-
if (present(msg)) msg = "Failed to open file '"//listed_contents//"'."; return
68+
if (present(iostat)) iostat = stat
69+
if (present(iomsg)) iomsg = "Failed to open file '"//listed_contents//"'."
70+
return
6571
end if
6672

6773
allocate(files(0))
6874
do
69-
read(unit, '(A)', iostat=iostat) line
70-
if (iostat /= 0) exit
75+
read(unit, '(A)', iostat=stat) line
76+
if (stat /= 0) exit
7177
files = [files, string_type(line)]
7278
end do
7379
close(unit, status="delete")
@@ -76,30 +82,31 @@ subroutine list_dir(dir, files, stat, msg)
7682
!> Version: experimental
7783
!>
7884
!> Run a command in the shell.
79-
subroutine run(command, stat, msg)
85+
!> [Specification](../page/specs/stdlib_io.html#run)
86+
subroutine run(command, iostat, iomsg)
8087
!> Command to run.
8188
character(len=*), intent(in) :: command
8289
!> Status of the operation.
83-
integer, intent(out), optional :: stat
90+
integer, intent(out), optional :: iostat
8491
!> Error message.
85-
character(len=:), allocatable, intent(out), optional :: msg
92+
character(len=:), allocatable, intent(out), optional :: iomsg
8693

8794
integer :: exitstat, cmdstat
8895
character(len=256) :: cmdmsg
8996

90-
if (present(stat)) stat = 0
97+
if (present(iostat)) iostat = 0
9198
exitstat = 0; cmdstat = 0
9299

93100
call execute_command_line(command, exitstat=exitstat, cmdstat=cmdstat, cmdmsg=cmdmsg)
94101
if (exitstat /= 0 .or. cmdstat /= 0) then
95-
if (present(stat)) then
102+
if (present(iostat)) then
96103
if (exitstat /= 0) then
97-
stat = exitstat
104+
iostat = exitstat
98105
else
99-
stat = cmdstat
106+
iostat = cmdstat
100107
end if
101108
end if
102-
if (present(msg) .and. trim(adjustl(cmdmsg)) /= '') msg = cmdmsg
109+
if (present(iomsg) .and. trim(adjustl(cmdmsg)) /= '') iomsg = cmdmsg
103110
end if
104111
end
105112
end

src/stdlib_io_zip.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ module stdlib_io_zip
1818
!> Version: experimental
1919
!>
2020
!> Create a zip file from a list of files.
21+
!> [Specification](../page/specs/stdlib_io.html#zip)
2122
subroutine zip(output_file, files, stat, msg, compressed)
2223
!> Name of the zip file to create.
2324
character(*), intent(in) :: output_file
@@ -68,6 +69,7 @@ subroutine zip(output_file, files, stat, msg, compressed)
6869
!> Version: experimental
6970
!>
7071
!> Extract a zip file to a directory.
72+
!> [Specification](../page/specs/stdlib_io.html#unzip)
7173
subroutine unzip(filename, outputdir, stat, msg)
7274
!> Name of the zip file to extract.
7375
character(len=*), intent(in) :: filename

0 commit comments

Comments
 (0)