Skip to content

Commit

Permalink
add stdlib_io_disp.fypp.
Browse files Browse the repository at this point in the history
  • Loading branch information
zoziha committed Sep 11, 2021
1 parent 323f700 commit 19dd5c6
Show file tree
Hide file tree
Showing 8 changed files with 799 additions and 6 deletions.
127 changes: 127 additions & 0 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -131,3 +131,130 @@ program demo_savetxt
call savetxt('example.dat', x)
end program demo_savetxt
```

## `disp` - display your data

### Status

Experimental

### Class

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

### Syntax

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

### Arguments

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

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

`brief`: Shall be a `logical` scalar.
This argument is `intent(in)` and `optional`.
Controls an abridged version of the `x` object is printed.

### Output

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.

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

If the `x` is present and of `real/complex` type, the data will retain four significant decimal places, like `(g0.4)`.

### Example

```fortran
program test_io_disp
use stdlib_io, only: disp
real(8) :: 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(c, header='disp(c):')
call disp(i, header='disp(i):')
call disp(l, header='disp(l):', brief=.true.)
call disp(c_3d(:,:,3), header='disp(c_3d(:,:,3)):', brief=.true.)
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.
disp(r):
[matrix size: 2×3]
-0.1000E-10 -0.1000E+11 1.000
1.000 1.000 1.000
disp(r(1,:))
[vector size: 3]
-0.1000E-10 -0.1000E+11 1.000
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)
disp(i):
[matrix size: 2×3]
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
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)
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)
```
1 change: 1 addition & 0 deletions src/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ set(fppFiles
stdlib_bitsets_64.fypp
stdlib_bitsets_large.fypp
stdlib_io.fypp
stdlib_io_disp.fypp
stdlib_linalg.fypp
stdlib_linalg_diag.fypp
stdlib_linalg_outer_product.fypp
Expand Down
12 changes: 9 additions & 3 deletions src/Makefile.manual
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ SRCFYPP = \
stdlib_bitsets_large.fypp \
stdlib_bitsets.fypp \
stdlib_io.fypp \
stdlib_io_disp.fypp \
stdlib_linalg.fypp \
stdlib_linalg_diag.fypp \
stdlib_linalg_outer_product.fypp \
Expand All @@ -27,8 +28,8 @@ SRCFYPP = \
stdlib_stats_moment_scalar.fypp \
stdlib_stats_var.fypp \
stdlib_math.fypp \
stdlib_math_linspace.fypp \
stdlib_math_logspace.fypp \
stdlib_math_linspace.fypp \
stdlib_math_logspace.fypp \
stdlib_stats_distribution_PRNG.fypp \
stdlib_string_type.fypp \
stdlib_string_type_constructor.fypp \
Expand Down Expand Up @@ -85,7 +86,12 @@ stdlib_io.o: \
stdlib_error.o \
stdlib_optval.o \
stdlib_kinds.o \
stdlib_ascii.o
stdlib_ascii.o \
stdlib_string_type.o
stdlib_io_disp.o: \
stdlib_strings.o \
stdlib_string_type.o \
stdlib_io.o
stdlib_linalg.o: \
stdlib_kinds.o
stdlib_linalg_diag.o: \
Expand Down
38 changes: 36 additions & 2 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -7,18 +7,52 @@ module stdlib_io
!! ([Specification](../page/specs/stdlib_io.html))

use stdlib_kinds, only: sp, dp, qp, &
int8, int16, int32, int64
int8, int16, int32, int64, lk, c_bool
use stdlib_error, only: error_stop
use stdlib_optval, only: optval
use stdlib_ascii, only: is_blank
use stdlib_string_type, only: string_type
implicit none
private
! Public API
public :: loadtxt, savetxt, open
public :: loadtxt, savetxt, open, disp

! Private API that is exposed so that we can test it in tests
public :: parse_mode


!> version: experimental
!>
!> Display a scalar, vector or matrix.
!> ([Specification](../page/specs/stdlib_io.html#disp-display-your-data-to-the-screen-or-another-output-unit))
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)}$
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
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
end interface disp

interface loadtxt
!! version: experimental
!!
Expand Down
Loading

0 comments on commit 19dd5c6

Please sign in to comment.