Skip to content

Commit 19dd5c6

Browse files
committed
add stdlib_io_disp.fypp.
1 parent 323f700 commit 19dd5c6

8 files changed

+799
-6
lines changed

Diff for: doc/specs/stdlib_io.md

+127
Original file line numberDiff line numberDiff line change
@@ -131,3 +131,130 @@ program demo_savetxt
131131
call savetxt('example.dat', x)
132132
end program demo_savetxt
133133
```
134+
135+
## `disp` - display your data
136+
137+
### Status
138+
139+
Experimental
140+
141+
### Class
142+
143+
Impure subroutine.
144+
145+
### Description
146+
147+
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`.
148+
149+
#### More details
150+
151+
```fortran
152+
call disp( A(i, j, 2, :, 1:10) [, header, unit, brief] ) !! `i, j, ...` can be determined by `do` loop.
153+
```
154+
155+
For `complex` type, the output format is `*(A25, 1X)`;
156+
For other types, the output format is `*(A12, 1X)`.
157+
158+
To prevent users from accidentally passing large-length arrays to `disp`, causing unnecessary io blockage:
159+
1. If the `brief` argument is not specified, `disp` will print **the brief array content with a length of `10*50` by default**.
160+
2. Specify `brief=.true.`, `disp` will print **the brief array content with a length of `5*5`**;
161+
3. Specify `brief=.false.`, `disp` will print **`all` the contents of the array**.
162+
163+
### Syntax
164+
165+
`call [[stdlib_io(module):disp(interface)]]([x, header, unit, brief])`
166+
167+
### Arguments
168+
169+
`x`: Shall be a `logical/integer/real/complex/string_type` scalar or `logical/integer/real/complex` and rank-1/rank-2 array.
170+
This argument is `intent(in)` and `optional`.
171+
172+
`header`: Shall be a `character(len=*)` scalar.
173+
This argument is `intent(in)` and `optional`.
174+
175+
`unit`: Shall be an `integer` scalar linked to an IO stream.
176+
This argument is `intent(in)` and `optional`.
177+
178+
`brief`: Shall be a `logical` scalar.
179+
This argument is `intent(in)` and `optional`.
180+
Controls an abridged version of the `x` object is printed.
181+
182+
### Output
183+
184+
The result is to print `header` and `x` on the screen (or another output `unit/file`) in this order.
185+
If `x` is a rank-1/rank-2 `array` type, the dimension length information of the `array` will also be outputted.
186+
187+
If `disp` is not passed any arguments, a blank line is printed.
188+
189+
If the `x` is present and of `real/complex` type, the data will retain four significant decimal places, like `(g0.4)`.
190+
191+
### Example
192+
193+
```fortran
194+
program test_io_disp
195+
196+
use stdlib_io, only: disp
197+
198+
real(8) :: r(2, 3)
199+
complex :: c(2, 3), c_3d(2, 100, 20)
200+
integer :: i(2, 3)
201+
logical :: l(10, 10)
202+
r = 1.; c = 1.; c_3d = 2.; i = 1; l = .true.
203+
r(1, 1) = -1.e-11
204+
r(1, 2) = -1.e10
205+
c(2, 2) = (-1.e10,-1.e10)
206+
c_3d(1,3,1) = (1000, 0.001)
207+
c_3d(1,3,2) = (1.e4, 100.)
208+
call disp('string', header='disp(string):')
209+
call disp('It is a note.')
210+
call disp()
211+
call disp(r, header='disp(r):')
212+
call disp(r(1,:), header='disp(r(1,:))')
213+
call disp(c, header='disp(c):')
214+
call disp(i, header='disp(i):')
215+
call disp(l, header='disp(l):', brief=.true.)
216+
call disp(c_3d(:,:,3), header='disp(c_3d(:,:,3)):', brief=.true.)
217+
call disp(c_3d(2,:,:), header='disp(c_3d(2,:,:)):', brief=.true.)
218+
219+
end program test_io_disp
220+
```
221+
**Results:**
222+
```fortran
223+
disp(string):
224+
string
225+
It is a note.
226+
227+
disp(r):
228+
[matrix size: 2×3]
229+
-0.1000E-10 -0.1000E+11 1.000
230+
1.000 1.000 1.000
231+
disp(r(1,:))
232+
[vector size: 3]
233+
-0.1000E-10 -0.1000E+11 1.000
234+
disp(c):
235+
[matrix size: 2×3]
236+
(1.000,0.000) (1.000,0.000) (1.000,0.000)
237+
(1.000,0.000) (-0.1000E+11,-0.1000E+11) (1.000,0.000)
238+
disp(i):
239+
[matrix size: 2×3]
240+
1 1 1
241+
1 1 1
242+
disp(l):
243+
[matrix size: 10×10]
244+
T T T ... T
245+
T T T ... T
246+
T T T ... T
247+
: : : : :
248+
T T T ... T
249+
disp(c_3d(:,:,3)):
250+
[matrix size: 2×100]
251+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
252+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
253+
disp(c_3d(2,:,:)):
254+
[matrix size: 100×20]
255+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
256+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
257+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
258+
: : : : :
259+
(2.000,0.000) (2.000,0.000) (2.000,0.000) ... (2.000,0.000)
260+
```

Diff for: src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ set(fppFiles
77
stdlib_bitsets_64.fypp
88
stdlib_bitsets_large.fypp
99
stdlib_io.fypp
10+
stdlib_io_disp.fypp
1011
stdlib_linalg.fypp
1112
stdlib_linalg_diag.fypp
1213
stdlib_linalg_outer_product.fypp

Diff for: src/Makefile.manual

+9-3
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ SRCFYPP = \
44
stdlib_bitsets_large.fypp \
55
stdlib_bitsets.fypp \
66
stdlib_io.fypp \
7+
stdlib_io_disp.fypp \
78
stdlib_linalg.fypp \
89
stdlib_linalg_diag.fypp \
910
stdlib_linalg_outer_product.fypp \
@@ -27,8 +28,8 @@ SRCFYPP = \
2728
stdlib_stats_moment_scalar.fypp \
2829
stdlib_stats_var.fypp \
2930
stdlib_math.fypp \
30-
stdlib_math_linspace.fypp \
31-
stdlib_math_logspace.fypp \
31+
stdlib_math_linspace.fypp \
32+
stdlib_math_logspace.fypp \
3233
stdlib_stats_distribution_PRNG.fypp \
3334
stdlib_string_type.fypp \
3435
stdlib_string_type_constructor.fypp \
@@ -85,7 +86,12 @@ stdlib_io.o: \
8586
stdlib_error.o \
8687
stdlib_optval.o \
8788
stdlib_kinds.o \
88-
stdlib_ascii.o
89+
stdlib_ascii.o \
90+
stdlib_string_type.o
91+
stdlib_io_disp.o: \
92+
stdlib_strings.o \
93+
stdlib_string_type.o \
94+
stdlib_io.o
8995
stdlib_linalg.o: \
9096
stdlib_kinds.o
9197
stdlib_linalg_diag.o: \

Diff for: src/stdlib_io.fypp

+36-2
Original file line numberDiff line numberDiff line change
@@ -7,18 +7,52 @@ module stdlib_io
77
!! ([Specification](../page/specs/stdlib_io.html))
88

99
use stdlib_kinds, only: sp, dp, qp, &
10-
int8, int16, int32, int64
10+
int8, int16, int32, int64, lk, c_bool
1111
use stdlib_error, only: error_stop
1212
use stdlib_optval, only: optval
1313
use stdlib_ascii, only: is_blank
14+
use stdlib_string_type, only: string_type
1415
implicit none
1516
private
1617
! Public API
17-
public :: loadtxt, savetxt, open
18+
public :: loadtxt, savetxt, open, disp
1819

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

23+
24+
!> version: experimental
25+
!>
26+
!> Display a scalar, vector or matrix.
27+
!> ([Specification](../page/specs/stdlib_io.html#disp-display-your-data-to-the-screen-or-another-output-unit))
28+
interface disp
29+
#:set DISP_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES &
30+
& + CMPLX_KINDS_TYPES + LOG_KINDS_TYPES
31+
#:set DISP_RANKS = range(0, 3)
32+
#:for k1, t1 in DISP_KINDS_TYPES
33+
#:for rank in DISP_RANKS
34+
module subroutine disp_${rank}$_${t1[0]}$${k1}$(x, header, unit, brief)
35+
${t1}$, intent(in) :: x${ranksuffix(rank)}$
36+
character(len=*), intent(in), optional :: header
37+
integer, intent(in), optional :: unit
38+
logical, intent(in), optional :: brief
39+
end subroutine disp_${rank}$_${t1[0]}$${k1}$
40+
#:endfor
41+
#:endfor
42+
module subroutine disp_character(x, header, unit, brief)
43+
character(len=*), intent(in), optional :: x
44+
character(len=*), intent(in), optional :: header
45+
integer, intent(in), optional :: unit
46+
logical, intent(in), optional :: brief
47+
end subroutine disp_character
48+
module subroutine disp_string_type(x, header, unit, brief)
49+
type(string_type), intent(in) :: x
50+
character(len=*), intent(in), optional :: header
51+
integer, intent(in), optional :: unit
52+
logical, intent(in), optional :: brief
53+
end subroutine disp_string_type
54+
end interface disp
55+
2256
interface loadtxt
2357
!! version: experimental
2458
!!

0 commit comments

Comments
 (0)