Skip to content

Commit

Permalink
Add documentation
Browse files Browse the repository at this point in the history
  • Loading branch information
minhqdao committed Aug 23, 2024
1 parent 6aa19aa commit 7b76756
Show file tree
Hide file tree
Showing 4 changed files with 212 additions and 25 deletions.
5 changes: 3 additions & 2 deletions doc/specs/stdlib_array.md
Original file line number Diff line number Diff line change
Expand Up @@ -147,7 +147,7 @@ Add an array of defined type and rank to a list of array wrappers.

#### Syntax

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

#### Class

Expand All @@ -170,6 +170,7 @@ Pure subroutine.
```fortran
{!example/io/example_save_npz.f90!}
```

### `get_values`

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

#### Syntax

`call ` [[stdlib_array(module):array_wrapper_type(type)]] `%` [[array_wrapper_type(type):get_values(bound)]] ` (wrapper, values[, stat, msg])`
`call ` [[stdlib_array(module):array_wrapper_type(type)]] `%` [[array_wrapper_type(type):get_values(bound)]] `(wrapper, values[, stat, msg])`

#### Class

Expand Down
185 changes: 181 additions & 4 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -136,11 +136,11 @@ Loads an `array` from a npy formatted binary file.

### Syntax

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

### Arguments

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

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


## `save_npy`

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

### Syntax

`call ` [[stdlib_io_npy(module):save_npy(interface)]] `(filename, array[, iostat][, iomsg])`
`call ` [[stdlib_io_np(module):save_npy(interface)]] `(filename, array[, iostat][, iomsg])`

### Arguments

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

## `load_npz`

### Status

Experimental

### Description

Populates an array of `array_wrapper_type` with the contents of an npz file.

### Syntax

`call ` [[stdlib_io_np(module):load_npz(interface)]] `(filename, arrays[, iostat][, iomsg][, tmp_dir])`

### Arguments

`filename`: Shall be a character expression containing the name of the npz file to load from. The argument is `intent(in)`.

`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)`.

`iostat`: Default integer, contains status of loading to file, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.

`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)`.

### Example

```fortran
{!example/io/example_load_npz.f90!}
```

## `save_npz`

### Status

Experimental

### Description

Saves an array of `array_wrapper_type` into a npz file.

### Syntax

`call ` [[stdlib_io_np(module):save_npz(interface)]] `(filename, arrays[, iostat][, iomsg][, compressed])`

### Arguments

`filename`: Shall be a character expression containing the name of the file that contains the arrays. This argument is `intent(in)`.

`arrays`: Shall be arrays of type `array_wrapper_type` that are meant to be saved to disk. This argument is `intent(in)`.

`iostat`: Default integer, contains status of saving to file, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.

`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.`.

### Example

```fortran
{!example/io/example_save_npz.f90!}
```

## `getline`

### Status
Expand Down Expand Up @@ -260,3 +323,117 @@ Provides formats for all kinds as defined in the `stdlib_kinds` module.
```fortran
{!example/io/example_fmt_constants.f90!}
```

## `zip`

### Status

Experimental

### Description

Compresses a file or directory into a zip archive.

### Syntax

`call ` [[stdlib_io_zip(module):zip(subroutine)]] ` (output_file, files[, stat][, msg][, compressed])`

### Arguments

`output_file`: Character expression representing the name of the zip file to create. This argument is `intent(in)`.

`files`: Array of `string_type` representing the names of the files to compress. This argument is `intent(in)`.

`stat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.

`compressed`: Logical expression that determines if the zip file should be compressed. The argument is `optional` and `intent(in)`. The default value is `.true.`.

## `unzip`

### Status

Experimental

### Description

Extracts a zip archive into a directory.

### Syntax

`call ` [[stdlib_io_zip(module):unzip(subroutine)]] ` (filename, outputdir[, stat][, msg])`

### Arguments

`filename`: Character expression representing the name of the zip file to extract. This argument is `intent(in)`.

`outputdir`: Character expression representing the name of the directory to extract the zip file to. This argument is `intent(in)`.

`stat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.

## `exists`

### Status

Experimental

### Description

Whether a file or directory exists at the given location in the filesystem.

### Syntax

`is_existing = ` [[stdlib_io_filesystem(module):exists(function)]] ` (filename)`

### Arguments

`filename`: Character expression representing the name of the file or directory to check for existence. This argument is `intent(in)`.

## `list_dir`

### Status

Experimental

### Description

Lists the contents of a directory.

### Syntax

`call ` [[stdlib_io_filesystem(module):list_dir(subroutine)]] ` (dir, files[, iostat][, iomsg])`

### Arguments

`dir`: Character expression representing the name of the directory to list. This argument is `intent(in)`.

`files`: Array of `string_type` representing the names of the files in the directory. This argument is `intent(out)`.

`iostat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.

## `run`

### Status

Experimental

### Description

Runs a command in the shell.

### Syntax

`call ` [[stdlib_io_filesystem(module):run(subroutine)]] ` (command[, iostat][, iomsg])`

### Arguments

`command`: Character expression representing the command to run. This argument is `intent(in)`.

`iostat`: Default integer, contains status of reading from unit, zero in case of success. This argument is `optional` and `intent(out)`.

`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)`.
45 changes: 26 additions & 19 deletions src/stdlib_io_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module stdlib_io_filesystem
!> Version: experimental
!>
!> Whether a file or directory exists at the given path.
!> [Specification](../page/specs/stdlib_io.html#exists)
logical function exists(filename)
!> Name of the file or directory.
character(len=*), intent(in) :: filename
Expand All @@ -30,44 +31,49 @@ logical function exists(filename)
!> Version: experimental
!>
!> List files and directories of a directory. Does not list hidden files.
subroutine list_dir(dir, files, stat, msg)
!> [Specification](../page/specs/stdlib_io.html#list_dir)
subroutine list_dir(dir, files, iostat, iomsg)
!> Directory to list.
character(len=*), intent(in) :: dir
!> List of files and directories.
type(string_type), allocatable, intent(out) :: files(:)
!> Status of listing.
integer, intent(out) :: stat
integer, optional, intent(out) :: iostat
!> Error message.
character(len=:), allocatable, optional, intent(out) :: msg
character(len=:), allocatable, optional, intent(out) :: iomsg

integer :: unit, iostat
integer :: unit, stat
character(len=256) :: line

stat = 0

if (.not. exists(temp_dir)) then
call run('mkdir '//temp_dir, stat)
if (stat /= 0) then
if (present(msg)) msg = "Failed to create temporary directory '"//temp_dir//"'."; return
if (present(iostat)) iostat = stat
if (present(iomsg)) iomsg = "Failed to create temporary directory '"//temp_dir//"'."
return
end if
end if

call run('ls '//dir//' > '//listed_contents, stat)
if (stat /= 0) then
if (present(msg)) then
msg = "Failed to list files in directory '"//dir//"'."; return
end if
if (present(iostat)) iostat = stat
if (present(iomsg)) iomsg = "Failed to list files in directory '"//dir//"'."
return
end if

open(newunit=unit, file=listed_contents, status='old', action='read', iostat=stat)
if (stat /= 0) then
if (present(msg)) msg = "Failed to open file '"//listed_contents//"'."; return
if (present(iostat)) iostat = stat
if (present(iomsg)) iomsg = "Failed to open file '"//listed_contents//"'."
return
end if

allocate(files(0))
do
read(unit, '(A)', iostat=iostat) line
if (iostat /= 0) exit
read(unit, '(A)', iostat=stat) line
if (stat /= 0) exit
files = [files, string_type(line)]
end do
close(unit, status="delete")
Expand All @@ -76,30 +82,31 @@ subroutine list_dir(dir, files, stat, msg)
!> Version: experimental
!>
!> Run a command in the shell.
subroutine run(command, stat, msg)
!> [Specification](../page/specs/stdlib_io.html#run)
subroutine run(command, iostat, iomsg)
!> Command to run.
character(len=*), intent(in) :: command
!> Status of the operation.
integer, intent(out), optional :: stat
integer, intent(out), optional :: iostat
!> Error message.
character(len=:), allocatable, intent(out), optional :: msg
character(len=:), allocatable, intent(out), optional :: iomsg

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

if (present(stat)) stat = 0
if (present(iostat)) iostat = 0
exitstat = 0; cmdstat = 0

call execute_command_line(command, exitstat=exitstat, cmdstat=cmdstat, cmdmsg=cmdmsg)
if (exitstat /= 0 .or. cmdstat /= 0) then
if (present(stat)) then
if (present(iostat)) then
if (exitstat /= 0) then
stat = exitstat
iostat = exitstat
else
stat = cmdstat
iostat = cmdstat
end if
end if
if (present(msg) .and. trim(adjustl(cmdmsg)) /= '') msg = cmdmsg
if (present(iomsg) .and. trim(adjustl(cmdmsg)) /= '') iomsg = cmdmsg
end if
end
end
2 changes: 2 additions & 0 deletions src/stdlib_io_zip.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ module stdlib_io_zip
!> Version: experimental
!>
!> Create a zip file from a list of files.
!> [Specification](../page/specs/stdlib_io.html#zip)
subroutine zip(output_file, files, stat, msg, compressed)
!> Name of the zip file to create.
character(*), intent(in) :: output_file
Expand Down Expand Up @@ -68,6 +69,7 @@ subroutine zip(output_file, files, stat, msg, compressed)
!> Version: experimental
!>
!> Extract a zip file to a directory.
!> [Specification](../page/specs/stdlib_io.html#unzip)
subroutine unzip(filename, outputdir, stat, msg)
!> Name of the zip file to extract.
character(len=*), intent(in) :: filename
Expand Down

0 comments on commit 7b76756

Please sign in to comment.