Skip to content

Commit a201a12

Browse files
committed
feat(stdlib_io): add print_array subroutine to print 2D arrays to output units
1 parent 6aa5177 commit a201a12

8 files changed

+493
-1
lines changed

doc/specs/stdlib_io.md

+35
Original file line numberDiff line numberDiff line change
@@ -305,3 +305,38 @@ Exceptions trigger an `error stop` unless the optional `err` argument is provide
305305
{!example/io/example_get_file.f90!}
306306
```
307307

308+
## `print_array` - Print an array to an output unit
309+
310+
### Status
311+
312+
Experimental
313+
314+
### Description
315+
316+
This subroutine interface prints a 2D array to a specified output unit.
317+
318+
### Syntax
319+
320+
`call [[stdlib_io(module):print_array(subroutine)]] (array[, unit][, fmt][, delimiter][, brief])`
321+
322+
### Class
323+
324+
Subroutine
325+
326+
### Arguments
327+
328+
`array`: Shall be a 2D array of `integer`, `real`, or `complex` type. It is an `intent(in)` argument.
329+
330+
`unit`: Shall be an integer containing the output unit. It is an `intent(in)` argument. The default is `6` (standard output).
331+
332+
`fmt`: Shall be a character string containing the format for printing the array. It is an `intent(in)` argument. The default is based on [the Formatting constants](#formatting-constants).
333+
334+
`delimiter`: Shall be a character string of length 1 containing the delimiter between array elements. It is an `intent(in)` argument. The default is a `" "` (space).
335+
336+
`brief`: Shall be a logical flag. If `.true.`, the array is printed in a brief format. The default is `.true.`.
337+
338+
### Example
339+
340+
```fortran
341+
{!./example/io/example_print_array.f90}
342+
```

example/io/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -6,3 +6,4 @@ ADD_EXAMPLE(loadtxt)
66
ADD_EXAMPLE(open)
77
ADD_EXAMPLE(savenpy)
88
ADD_EXAMPLE(savetxt)
9+
ADD_EXAMPLE(print_array)

example/io/example_print_array.f90

+16
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
program example_io_print_array
2+
3+
use stdlib_io, only: print_array
4+
implicit none
5+
6+
integer, dimension(6, 3) :: array = reshape([1, 2, 3, 4, 5, 6, &
7+
7, 8, 9, 10, 11, 12, &
8+
13, 14, 15, 16, 17, 18], [6, 3])
9+
10+
print "(a)", "=== print_array 1 ==="
11+
call print_array(array, unit=6, fmt='(i3)', delimiter='|', brief=.true.)
12+
13+
print "(a)", "=== print_array 2 ==="
14+
call print_array(array(:1, :))
15+
16+
end program example_io_print_array

src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ set(fppFiles
2424
stdlib_io_npy.fypp
2525
stdlib_io_npy_load.fypp
2626
stdlib_io_npy_save.fypp
27+
stdlib_io_print_array.fypp
2728
stdlib_kinds.fypp
2829
stdlib_linalg.fypp
2930
stdlib_linalg_diag.fypp

src/stdlib_io.fypp

+17-1
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ module stdlib_io
1616
implicit none
1717
private
1818
! Public API
19-
public :: loadtxt, savetxt, open, get_line, get_file
19+
public :: loadtxt, savetxt, open, get_line, get_file, print_array
2020

2121
!! version: experimental
2222
!!
@@ -102,6 +102,22 @@ module stdlib_io
102102
#:endfor
103103
end interface
104104

105+
interface print_array
106+
!! version: experimental
107+
!!
108+
!! Prints a 2D array to an output unit
109+
!! ([Specification](../page/specs/stdlib_io.html#print_array))
110+
#:for k1, t1 in KINDS_TYPES
111+
module subroutine print_array_${t1[0]}$${k1}$(array, unit, fmt, delimiter, brief)
112+
${t1}$, intent(in) :: array(:, :)
113+
integer, intent(in), optional :: unit
114+
character(len=*), intent(in), optional :: fmt
115+
character(len=1), intent(in), optional :: delimiter
116+
logical, intent(in), optional :: brief
117+
end subroutine print_array_${t1[0]}$${k1}$
118+
#:endfor
119+
end interface
120+
105121
contains
106122

107123
#:for k1, t1 in KINDS_TYPES

src/stdlib_io_print_array.fypp

+88
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,88 @@
1+
#:include "common.fypp"
2+
#:set KINDS_TYPES = REAL_KINDS_TYPES + CMPLX_KINDS_TYPES + INT_KINDS_TYPES
3+
submodule(stdlib_io) stdlib_io_print_array
4+
5+
use, intrinsic :: iso_fortran_env, only: output_unit
6+
implicit none
7+
8+
contains
9+
10+
#:for k1, t1 in KINDS_TYPES
11+
module subroutine print_array_${t1[0]}$${k1}$(array, unit, fmt, delimiter, brief)
12+
${t1}$, intent(in) :: array(:, :)
13+
integer, intent(in), optional :: unit
14+
character(len=*), intent(in), optional :: fmt
15+
character(len=1), intent(in), optional :: delimiter
16+
logical, intent(in), optional :: brief
17+
18+
integer :: i, j, unit_, shape_(2)
19+
character(len=:), allocatable :: fmt_
20+
character(len=1) :: delimiter_
21+
character(len=3) :: delim_str
22+
logical :: brief_
23+
24+
shape_ = shape(array)
25+
if (any(shape_ == 0)) return
26+
unit_ = optval(unit, output_unit)
27+
delimiter_ = optval(delimiter, delimiter_default)
28+
delim_str = "'"//delimiter_//"'"
29+
brief_ = optval(brief, .true.)
30+
if (present(fmt)) then
31+
fmt_ = "(*"//fmt(1:len(fmt) - 1)//",:,"//delim_str//"))"
32+
else
33+
#:if 'real' in t1
34+
fmt_ = "(*"//FMT_REAL_${k1}$ (1:len(FMT_REAL_${k1}$) - 1)//",:,"//delim_str//"))"
35+
#:elif 'complex' in t1
36+
fmt_ = "(*"//FMT_COMPLEX_${k1}$ (1:11)//delim_str//FMT_COMPLEX_${k1}$ (14:23)//",:,"//delim_str//"))"
37+
#:elif 'integer' in t1
38+
fmt_ = "(*"//FMT_INT(1:len(FMT_INT) - 1)//",:,"//delim_str//"))"
39+
#:endif
40+
end if
41+
42+
if (brief_) then
43+
44+
if (shape_(1) > 5) then
45+
if (shape_(2) > 5) then
46+
do i = 1, 3
47+
write (unit_, fmt=fmt_, advance='no') array(i, :3)
48+
write (unit_, fmt='(a)', advance='no') delimiter_//"..."//delimiter_
49+
write (unit_, fmt=fmt_) array(i, shape_(2))
50+
end do
51+
write (unit_, fmt='(a)') ":"
52+
write (unit_, fmt=fmt_, advance='no') array(shape_(1), :3)
53+
write (unit_, fmt='(a)', advance='no') delimiter_//"..."//delimiter_
54+
write (unit_, fmt=fmt_) array(shape_(1), shape_(2))
55+
else
56+
do i = 1, 3
57+
write (unit_, fmt=fmt_) array(i, :)
58+
end do
59+
write (unit_, fmt='(a)') ":"
60+
write (unit_, fmt=fmt_) array(shape_(1), :)
61+
62+
end if
63+
else
64+
if (shape_(2) > 5) then
65+
do i = 1, shape_(1)
66+
write (unit_, fmt=fmt_, advance='no') array(i, :3)
67+
write (unit_, fmt='(a)', advance='no') delimiter_//"..."//delimiter_
68+
write (unit_, fmt=fmt_) array(i, shape_(2))
69+
end do
70+
else
71+
do i = 1, shape_(1)
72+
write (unit_, fmt=fmt_) array(i, :)
73+
end do
74+
end if
75+
end if
76+
77+
else
78+
79+
do i = 1, shape_(1)
80+
write (unit_, fmt=fmt_) array(i, :)
81+
end do
82+
83+
end if
84+
85+
end subroutine print_array_${t1[0]}$${k1}$
86+
#:endfor
87+
88+
end submodule stdlib_io_print_array

test/io/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -17,3 +17,4 @@ ADDTEST(get_line)
1717
ADDTEST(npy)
1818
ADDTEST(open)
1919
ADDTEST(parse_mode)
20+
ADDTEST(print_array)

0 commit comments

Comments
 (0)