Skip to content

Commit 92aca11

Browse files
committed
Add some docs
1 parent a22f401 commit 92aca11

File tree

6 files changed

+45
-8
lines changed

6 files changed

+45
-8
lines changed

src/stdlib_array.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
#:set RANKS = range(1, MAXRANK + 1)
55
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES
66

7-
!> Module for index manipulation and general array handling
7+
!> Module for general array handling and index manipulation.
88
!>
99
!> The specification of this module is available [here](../page/specs/stdlib_array.html).
1010
module stdlib_array

src/stdlib_filesystem.f90

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
! SPDX-Identifier: MIT
2+
3+
!> Interaction with the filesystem.
14
module stdlib_filesystem
25
use stdlib_string_type, only: string_type
36
implicit none
@@ -10,7 +13,11 @@ module stdlib_filesystem
1013

1114
contains
1215

16+
!> Version: experimental
17+
!>
18+
!> Whether a file or directory exists at the given path.
1319
logical function exists(filename)
20+
!> Name of the file or directory.
1421
character(len=*), intent(in) :: filename
1522

1623
inquire(file=filename, exist=exists)
@@ -20,11 +27,17 @@ logical function exists(filename)
2027
#endif
2128
end
2229

30+
!> Version: experimental
31+
!>
2332
!> List files and directories of a directory. Does not list hidden files.
2433
subroutine list_dir(dir, files, stat, msg)
34+
!> Directory to list.
2535
character(len=*), intent(in) :: dir
36+
!> List of files and directories.
2637
type(string_type), allocatable, intent(out) :: files(:)
38+
!> Status of listing.
2739
integer, intent(out) :: stat
40+
!> Error message.
2841
character(len=:), allocatable, optional, intent(out) :: msg
2942

3043
integer :: unit, iostat
@@ -60,9 +73,15 @@ subroutine list_dir(dir, files, stat, msg)
6073
close(unit, status="delete")
6174
end
6275

76+
!> Version: experimental
77+
!>
78+
!> Run a command in the shell.
6379
subroutine run(command, stat, msg)
80+
!> Command to run.
6481
character(len=*), intent(in) :: command
82+
!> Status of the operation.
6583
integer, intent(out), optional :: stat
84+
!> Error message.
6685
character(len=:), allocatable, intent(out), optional :: msg
6786

6887
integer :: exitstat, cmdstat

src/stdlib_io_np.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
#:set RANKS = range(1, MAXRANK + 1)
55
#:set KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES + CMPLX_KINDS_TYPES
66

7-
!> Description of the npy format taken from
7+
!> Description of the npy and npz formats taken from
88
!> https://numpy.org/doc/stable/reference/generated/numpy.lib.format.html
99
!>
1010
!>## Format Version 1.0

src/stdlib_io_np_load.fypp

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -101,10 +101,7 @@ contains
101101
#:endfor
102102
#:endfor
103103

104-
!> Version: experimental
105-
!>
106104
!> Load multidimensional arrays from a compressed or uncompressed npz file.
107-
!> ([Specification](../page/specs/stdlib_io.html#load_npz))
108105
module subroutine load_npz_to_arrays(filename, arrays, iostat, iomsg, tmp_dir)
109106
character(len=*), intent(in) :: filename
110107
type(array_wrapper_type), allocatable, intent(out) :: arrays(:)
@@ -145,11 +142,17 @@ contains
145142
end if
146143
end
147144

145+
!> Load arrays from unzipped files.
148146
subroutine load_unzipped_files_to_arrays(files, dir, arrays, stat, msg)
147+
!> List of files to load arrays from.
149148
type(string_type), intent(in) :: files(:)
149+
!> Directory containing the files.
150150
character(len=*), intent(in) :: dir
151+
!> Array of array wrappers to store the loaded arrays.
151152
type(array_wrapper_type), allocatable, intent(out) :: arrays(:)
153+
!> Status of the operation. Zero on success.
152154
integer, intent(out) :: stat
155+
!> Error message in case of non-zero status.
153156
character(len=:), allocatable, intent(out) :: msg
154157

155158
integer :: i, io

src/stdlib_io_np_save.fypp

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -135,10 +135,7 @@ contains
135135
#:endfor
136136
#:endfor
137137

138-
!> Version: experimental
139-
!>
140138
!> Save multidimensional arrays to a compressed or an uncompressed npz file.
141-
!> ([Specification](../page/specs/stdlib_io.html#save_npz))
142139
module subroutine save_arrays_to_npz(filename, arrays, iostat, iomsg, compressed)
143140
!> Name of the npz file to save to.
144141
character(len=*), intent(in) :: filename

src/stdlib_io_zip.f90

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,6 @@
1+
! SPDX-Identifier: MIT
2+
3+
!> Handling of zip files including creation and extraction.
14
module stdlib_io_zip
25
use stdlib_filesystem, only: exists, run, temp_dir
36
use stdlib_string_type, only: string_type, char
@@ -12,11 +15,19 @@ module stdlib_io_zip
1215

1316
contains
1417

18+
!> Version: experimental
19+
!>
20+
!> Create a zip file from a list of files.
1521
subroutine zip(output_file, files, stat, msg, compressed)
22+
!> Name of the zip file to create.
1623
character(*), intent(in) :: output_file
24+
!> List of files to include in the zip file.
1725
type(string_type), intent(in) :: files(:)
26+
!> Optional error status of zipping, zero on success.
1827
integer, intent(out), optional :: stat
28+
!> Optional error message.
1929
character(len=:), allocatable, intent(out), optional :: msg
30+
!> If true, the file is saved in compressed format. The default is true.
2031
logical, intent(in), optional :: compressed
2132

2233
integer :: run_stat, i
@@ -54,10 +65,17 @@ subroutine zip(output_file, files, stat, msg, compressed)
5465
end if
5566
end
5667

68+
!> Version: experimental
69+
!>
70+
!> Extract a zip file to a directory.
5771
subroutine unzip(filename, outputdir, stat, msg)
72+
!> Name of the zip file to extract.
5873
character(len=*), intent(in) :: filename
74+
!> Directory to extract the zip file to.
5975
character(len=*), intent(in), optional :: outputdir
76+
!> Optional error status of unzipping, zero on success.
6077
integer, intent(out), optional :: stat
78+
!> Optional error message.
6179
character(len=:), allocatable, intent(out), optional :: msg
6280

6381
integer :: run_stat

0 commit comments

Comments
 (0)