Skip to content

Commit

Permalink
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Redesign and update disp.
Browse files Browse the repository at this point in the history
zoziha committed Nov 9, 2021

Verified

This commit was created on GitHub.com and signed with GitHub’s verified signature. The key has expired.
1 parent 38edc33 commit 4bae170
Showing 4 changed files with 593 additions and 477 deletions.
114 changes: 55 additions & 59 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
@@ -132,7 +132,7 @@ program demo_savetxt
end program demo_savetxt
```

## `disp` - display your data
## `disp` - display the value of the vairable

### Status

@@ -144,49 +144,45 @@ Impure subroutine.

### Description

Outputs a `logical/integer/real/complex/character/string_type` scalar or `logical/integer/real/complex` and rank-1/rank-2 array to the screen or a file `unit`.

#### More details

```fortran
call disp( A(i, j, 2, :, 1:10) [, header, unit, brief] ) !! `i, j, ...` can be determined by `do` loop.
```

For `complex` type, the output format is `*(A25, 1X)`;
For other types, the output format is `*(A12, 1X)`.

To prevent users from accidentally passing large-length arrays to `disp`, causing unnecessary io blockage:
1. If the `brief` argument is not specified, `disp` will print **the brief array content with a length of `10*50` by default**.
2. Specify `brief=.true.`, `disp` will print **the brief array content with a length of `5*5`**;
3. Specify `brief=.false.`, `disp` will print **`all` the contents of the array**.
Outputs a `logical/integer/real/complex/character/string_type` scalar,
or `logical/integer/real/complex/string_type` and rank-1/rank-2 array to the screen or a file `unit`.

### Syntax

`call [[stdlib_io(module):disp(interface)]]([x, header, unit, brief])`
`call [[stdlib_io(module):disp(interface)]]( [x, header, unit, brief, format, width, sep] )`

### Arguments

`x`: Shall be a `logical/integer/real/complex/string_type` scalar or `logical/integer/real/complex` and rank-1/rank-2 array.
- `x`: Shall be a `logical/integer/real/complex/character(len=*)/string_type` scalar or `logical/integer/real/complex/string_type` and rank-1/rank-2 array.
This argument is `intent(in)` and `optional`.

`header`: Shall be a `character(len=*)` scalar.
- `header`: Shall be a `character(len=*)` scalar.
This argument is `intent(in)` and `optional`.

`unit`: Shall be an `integer` scalar linked to an IO stream.
This argument is `intent(in)` and `optional`.
- `unit`: Shall be an `integer` scalar, linked to an IO stream.
This argument is `intent(in)` and `optional`.<br>
The default value is `output_unit` from `iso_fortran_env` module.

`brief`: Shall be a `logical` scalar.
This argument is `intent(in)` and `optional`.
Controls an abridged version of the `x` object is printed.
- `brief`: Shall be a `logical` scalar, controls an abridged version of the `x` array to be outputed.
This argument is `intent(in)` and `optional`.<br>
The default value is `.false.`

### Output
- `format`: Shall be a `character(len=*)` scalar.
This argument is `intent(in)` and `optional`.<br>
The default value is `g0.4`.

- `width`: Shall be an `integer` scalar, controls the outputed maximum width (`>=80`).
This argument is `intent(in)` and `optional`.<br>
The default value is `80`.

The result is to print `header` and `x` on the screen (or another output `unit/file`) in this order.
If `x` is a rank-1/rank-2 `array` type, the dimension length information of the `array` will also be outputted.
- `sep`: Shall be a `character(len=*)` scalar, separator.
This argument is `intent(in)` and `optional`.<br>
The default value is "&ensp;&ensp;", two spaces.

If `disp` is not passed any arguments, a blank line is printed.
### Output

If the `x` is present and of `real/complex` type, the data will retain four significant decimal places, like `(g0.4)`.
The result is to print `header` and `x` on the screen (or another output `unit/file`) in this order.<br>
If `disp` is not passed any arguments, a blank line will be printed.

### Example

@@ -195,66 +191,66 @@ program test_io_disp
use stdlib_io, only: disp
real(8) :: r(2, 3)
real :: r(2, 3)
complex :: c(2, 3), c_3d(2, 100, 20)
integer :: i(2, 3)
logical :: l(10, 10)
r = 1.; c = 1.; c_3d = 2.; i = 1; l = .true.
r(1, 1) = -1.e-11
r(1, 2) = -1.e10
c(2, 2) = (-1.e10,-1.e10)
c_3d(1,3,1) = (1000, 0.001)
c_3d(1,3,2) = (1.e4, 100.)
call disp('string', header='disp(string):')
call disp('It is a note.')
call disp()
call disp(r, header='disp(r):')
call disp(r(1,:), header='disp(r(1,:))')
call disp(r(1,:), header='disp(r(1,:))', format="f6.2")
call disp(c, header='disp(c):')
call disp(i, header='disp(i):')
call disp(i, header='disp(i):', sep=",")
call disp(l, header='disp(l):', brief=.true.)
call disp(c_3d(:,:,3), header='disp(c_3d(:,:,3)):', brief=.true.)
call disp(c_3d(:,3,1:10), header='disp(c_3d(:,3,1:10)):', width=100)
call disp(c_3d(2,:,:), header='disp(c_3d(2,:,:)):', brief=.true.)
end program test_io_disp
```
**Results:**
```fortran
disp(string):
string
It is a note.
string
It is a note.
disp(r):
[matrix size: 2×3]
-0.1000E-10 -0.1000E+11 1.000
1.000 1.000 1.000
1.000 1.000 1.000
1.000 1.000 1.000
disp(r(1,:))
[vector size: 3]
-0.1000E-10 -0.1000E+11 1.000
1.00 1.00 1.00
disp(c):
[matrix size: 2×3]
(1.000,0.000) (1.000,0.000) (1.000,0.000)
(1.000,0.000) (-0.1000E+11,-0.1000E+11) (1.000,0.000)
(1.000,0.000) (1.000,0.000) (1.000,0.000)
(1.000,0.000) (1.000,0.000) (1.000,0.000)
disp(i):
[matrix size: 2×3]
1 1 1
1 1 1
1, 1, 1,
1, 1, 1,
disp(l):
[matrix size: 10×10]
T T T ... T
T T T ... T
T T T ... T
: : : : :
T T T ... T
T T T .. T
T T T .. T
T T T .. T
: : : : :
T T T .. T
disp(c_3d(:,:,3)):
[matrix size: 2×100]
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
[matrix size: 2×10]
(1000.,0.1000E-2) (2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000) &
(2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000) &
(2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000) (2.000,0.000)
disp(c_3d(2,:,:)):
[matrix size: 100×20]
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
: : : : :
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) .. (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) .. (2.000,0.000)
(2.000,0.000) (2.000,0.000) (2.000,0.000) .. (2.000,0.000)
: : : : :
(2.000,0.000) (2.000,0.000) (2.000,0.000) .. (2.000,0.000)
```
45 changes: 22 additions & 23 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
@@ -34,32 +34,31 @@ module stdlib_io
!>
!> Display a scalar, vector or matrix.
!> ([Specification](../page/specs/stdlib_io.html#disp-display-your-data))
#! Displays a scalar or array value nicely
interface disp
#:set DISP_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES &
& + CMPLX_KINDS_TYPES + LOG_KINDS_TYPES
#:set DISP_RANKS = range(0, 3)
#:for k1, t1 in DISP_KINDS_TYPES
#:for rank in DISP_RANKS
module subroutine disp_${rank}$_${t1[0]}$${k1}$(x, header, unit, brief)
${t1}$, intent(in) :: x${ranksuffix(rank)}$
#:set ALL_KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES + LOG_KINDS_TYPES + STRING_KINDS_TYPES
module subroutine disp_char(x, header, unit, brief, format, width, sep)
character(*), intent(in), optional :: x
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
end subroutine disp_${rank}$_${t1[0]}$${k1}$
#:endfor
#:endfor
module subroutine disp_character(x, header, unit, brief)
character(len=*), intent(in), optional :: x
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
end subroutine disp_char
#:for r1 in range(0, 3)
#:for k1, t1 in ALL_KINDS_TYPES
module subroutine disp_${r1}$_${t1[0]}$${k1}$(x, header, unit, brief, format, width, sep)
${t1}$, intent(in) :: x${ranksuffix(r1)}$
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
end subroutine disp_character
module subroutine disp_string_type(x, header, unit, brief)
type(string_type), intent(in) :: x
character(len=*), intent(in), optional :: header
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
end subroutine disp_string_type
integer, intent(in), optional :: unit
logical, intent(in), optional :: brief
character(len=*), intent(in), optional :: format
integer, intent(in), optional :: width
character(len=*), intent(in), optional :: sep
end subroutine disp_${r1}$_${t1[0]}$${k1}$
#:endfor
#:endfor
end interface disp

interface loadtxt
Loading

0 comments on commit 4bae170

Please sign in to comment.