Skip to content
Closed
Show file tree
Hide file tree
Changes from 1 commit
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
9 changes: 6 additions & 3 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -20,27 +20,30 @@ module stdlib_io
public :: parse_mode

interface disp
!! version: experimental
!!
!! Quickly display strings, scalars and low-dimensional arrays to the default output_unit
!! ([Specification](../page/specs/stdlib_io.html#description))
#:set DISP_KINDS_TYPES = REAL_KINDS_TYPES + INT_KINDS_TYPES &
& + CMPLX_KINDS_TYPES + LOG_KINDS_TYPES
#:set DISP_RANKS = range(0, 4)
#:for kind, type in DISP_KINDS_TYPES
#:for rank in DISP_RANKS
#:if rank != 3
impure module subroutine disp_${rank}$_${type[0]}$${kind}$(val, string)
module subroutine disp_${rank}$_${type[0]}$${kind}$(val, string)
${type}$, intent(in) :: val${ranksuffix(rank)}$
character(len=*), intent(in), optional :: string
end subroutine disp_${rank}$_${type[0]}$${kind}$
#:else
impure module subroutine disp_${rank}$_${type[0]}$${kind}$(val, dim, string)
module subroutine disp_${rank}$_${type[0]}$${kind}$(val, dim, string)
${type}$, intent(in) :: val${ranksuffix(rank)}$
integer, intent(in) :: dim
character(len=*), intent(in), optional :: string
end subroutine disp_${rank}$_${type[0]}$${kind}$
#:endif
#:endfor
#:endfor
impure module subroutine disp_str(val, string)
module subroutine disp_str(val, string)
character(len=*), intent(in), optional :: val
character(len=*), intent(in), optional :: string
end subroutine disp_str
Expand Down
46 changes: 25 additions & 21 deletions src/stdlib_io_disp.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -3,55 +3,57 @@

submodule (stdlib_io) stdlib_io_disp

use, non_intrinsic :: stdlib_strings, only: format_string
use stdlib_ascii, only: to_string
use stdlib_strings, only: format_string
implicit none
character(len=*), parameter :: fmt_r = '(*(g11.4, 1x))'
character(len=*), parameter :: fmt_c = '(*(g23.4, 1x))'
character(len=*), parameter :: fmt_r = '(*(g12.4, 1x))'
character(len=*), parameter :: fmt_c = '(*(g25.0, 1x))'

contains

#:for kind, type in RIL_KINDS_TYPES
module procedure disp_0_${type[0]}$${kind}$
!! Disp ${type}$ variable to default output_unit
if(present(string)) print *, trim(string)
print fmt_r, val
end procedure disp_0_${type[0]}$${kind}$

module procedure disp_1_${type[0]}$${kind}$
integer :: i, m
m = size(val)
!! Disp ${type}$ vector variable to default output_unit
if(present(string)) print *, trim(string)
print fmt_r, (val(i), i=1,m)
print fmt_r, val(:)
end procedure disp_1_${type[0]}$${kind}$

module procedure disp_2_${type[0]}$${kind}$
integer :: i, j, m, n
!! Disp ${type}$ 2D array variable to default output_unit
integer :: i, m
m = size(val, 1)
n = size(val, 2)
if(present(string)) print *, trim(string)
do i = 1, m
print fmt_r, (val(i,j), j=1, n)
print fmt_r, val(i,:)
end do
end procedure disp_2_${type[0]}$${kind}$

module procedure disp_3_${type[0]}$${kind}$
!! Disp ${type}$ 3D array variable to default output_unit
integer :: i, dim1, dim2, dim3
dim1 = size(val, 1)
dim2 = size(val, 2)
dim3 = size(val, 3)
if(present(string)) print *, trim(string)
if(dim == 1) then
do i = 1, dim1
print *, 'Slice ('//format_string(i)//',:,:):'
print *, 'Slice ('//to_string(i)//',:,:):'
call disp_2_${type[0]}$${kind}$(val(i, :, :))
end do
elseif(dim == 2) then
do i = 1, dim2
print *, 'Slice (:,'//format_string(i)//',:):'
print *, 'Slice (:,'//to_string(i)//',:):'
call disp_2_${type[0]}$${kind}$(val(:, i, :))
end do
elseif (dim == 3) then
do i = 1, dim3
print *, 'Slice (:,:,'//format_string(i)//'):'
print *, 'Slice (:,:,'//to_string(i)//'):'
call disp_2_${type[0]}$${kind}$(val(:, :, i))
end do
else
Expand All @@ -62,49 +64,50 @@ contains

#:for kind, type in CMPLX_KINDS_TYPES
module procedure disp_0_${type[0]}$${kind}$
!! Disp ${type}$ variable to default output_unit
if(present(string)) print *, trim(string)
print fmt_c, format_string(cmplx(real(val), &
aimag(val)), '(g11,4)')
print fmt_c, format_string(val, '(g0.4)')
end procedure disp_0_${type[0]}$${kind}$

module procedure disp_1_${type[0]}$${kind}$
!! Disp ${type}$ vector variable to default output_unit
integer :: i, m
m = size(val)
if(present(string)) print *, trim(string)
print fmt_c, (format_string(cmplx(real(val(i)), &
aimag(val(i))), '(g11.4)'), i=1, m)
print fmt_c, (format_string(val(i), '(g0.4)'), i=1, m)
end procedure disp_1_${type[0]}$${kind}$

module procedure disp_2_${type[0]}$${kind}$
!! Disp ${type}$ 2D array variable to default output_unit
integer :: i, j, m, n
m = size(val, 1)
n = size(val, 2)
if(present(string)) print *, trim(string)
do i = 1, m
print fmt_c, (format_string(cmplx(real(val(i, j)), &
aimag(val(i, j))), '(g11.4)'), j=1, n)
print fmt_c, (format_string(val(i, j), '(g0.4)'), j=1, n)
end do
end procedure disp_2_${type[0]}$${kind}$

module procedure disp_3_${type[0]}$${kind}$
!! Disp ${type}$ 3D array variable to default output_unit
integer :: i, dim1, dim2, dim3
dim1 = size(val, 1)
dim2 = size(val, 2)
dim3 = size(val, 3)
if(present(string)) print *, trim(string)
if(dim == 1) then
do i = 1, dim1
print *, 'Slice ('//format_string(i)//',:,:):'
print *, 'Slice ('//to_string(i)//',:,:):'
call disp_2_${type[0]}$${kind}$(val(i, :, :))
end do
elseif(dim == 2) then
do i = 1, dim2
print *, 'Slice (:,'//format_string(i)//',:):'
print *, 'Slice (:,'//to_string(i)//',:):'
call disp_2_${type[0]}$${kind}$(val(:, i, :))
end do
elseif (dim == 3) then
do i = 1, dim3
print *, 'Slice (:,:,'//format_string(i)//'):'
print *, 'Slice (:,:,'//to_string(i)//'):'
call disp_2_${type[0]}$${kind}$(val(:, :, i))
end do
else
Expand All @@ -114,6 +117,7 @@ contains
#:endfor

module procedure disp_str
!! Disp character variable to default output_unit
if(present(string)) print *, trim(string)
if(present(val)) then
print *, trim(val)
Expand Down
8 changes: 5 additions & 3 deletions src/tests/io/test_io_disp.f90
Original file line number Diff line number Diff line change
@@ -1,15 +1,17 @@
program test_io_disp
use, non_intrinsic :: stdlib_io, only: disp
implicit none
real :: r(2, 3)
real(8) :: r(2, 3)
complex :: c(2, 3), c_3d(2, 3, 2)
integer :: i(2, 3)
logical :: l(2, 3)

r = 1.; c = 1.; c_3d = 2.; i = 1; l = .true.
r(1, 1) = (1.e-11, 1.0e-4)
c(2, 2) = 10.e5
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', 'disp(string):')
call disp('It is a note.')
call disp()
Expand Down