Skip to content
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,9 @@ Changes to existing modules
[#562](https://github.com/fortran-lang/stdlib/pull/562)
- support for quadruple precision made optional
[#565](https://github.com/fortran-lang/stdlib/pull/565)
- change in module `stdlib_io`
- Modified format constants, and made public
[#617](https://github.com/fortran-lang/stdlib/pull/617)


# Version 0.1.0
Expand Down
42 changes: 42 additions & 0 deletions doc/specs/stdlib_io.md
Original file line number Diff line number Diff line change
Expand Up @@ -273,3 +273,45 @@ program demo_getline
end do
end program demo_getline
```

## Formatting constants

### Status

Experimental

### Description

Formatting constants for printing out integer, floating point, and complex numbers at their full precision.
Provides formats for all kinds as defined in the `stdlib_kinds` module.

### Example

```fortran
program demo_fmt_constants
use, stdlib_kinds, only : int32, int64, sp, dp
use stdlib_io, only : FMT_INT, FMT_REAL_SP, FMT_REAL_DP, FMT_COMPLEX_SP, FMT_COMPLEX_DP
implicit none

integer(kind=int32) :: i32
integer(kind=int64) :: i64
real(kind=sp) :: r32
real(kind=dp) :: r64
complex(kind=sp) :: c32
complex(kind=dp) :: c64

i32 = 100_int32
i64 = 100_int64
r32 = 100.0_sp
r64 = 100.0_dp
c32 = cmplx(100.0_sp, kind=sp)
c64 = cmplx(100.0_dp, kind=dp)

print "(2("//FMT_INT//",1x))", i32, i64 ! outputs: 100 100
print FMT_REAL_SP, r32 ! outputs: 1.00000000E+02
print FMT_REAL_DP, r64 ! outputs: 1.0000000000000000E+002
print FMT_COMPLEX_SP, c32 ! outputs: 1.00000000E+02 0.00000000E+00
print FMT_COMPLEX_DP, c64 ! outputs: 1.0000000000000000E+002 0.0000000000000000E+000

end program demo_fmt_constants
```
45 changes: 30 additions & 15 deletions src/stdlib_io.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -21,17 +21,32 @@ module stdlib_io
! Private API that is exposed so that we can test it in tests
public :: parse_mode

! Format strings with edit descriptors for each type and kind
!> Version: experimental
!>
!> Format strings with edit descriptors for each type and kind
!> ([Specification](../page/specs/stdlib_io.html))
character(*), parameter :: &
FMT_INT = '(*(i0,1x))', &
FMT_REAL_SP = '(*(es15.8e2,1x))', &
FMT_REAL_DP = '(*(es24.16e3,1x))', &
FMT_REAL_XDP = '(*(es26.18e3,1x))', &
FMT_REAL_QP = '(*(es44.35e4,1x))', &
FMT_COMPLEX_SP = '(*(es15.8e2,1x,es15.8e2))', &
FMT_COMPLEX_DP = '(*(es24.16e3,1x,es24.16e3))', &
FMT_COMPLEX_XDP = '(*(es26.18e3,1x,es26.18e3))', &
FMT_COMPLEX_QP = '(*(es44.35e4,1x,es44.35e4))'
!> Format string for integers
FMT_INT = '(i0)', &
!> Format string for single precision real numbers
FMT_REAL_SP = '(es15.8e2)', &
!> Format string for souble precision real numbers
FMT_REAL_DP = '(es24.16e3)', &
!> Format string for extended double precision real numbers
FMT_REAL_XDP = '(es26.18e3)', &
!> Format string for quadruple precision real numbers
FMT_REAL_QP = '(es44.35e4)', &
!> Format string for single precision complex numbers
FMT_COMPLEX_SP = '(es15.8e2,1x,es15.8e2)', &
!> Format string for double precision complex numbers
FMT_COMPLEX_DP = '(es24.16e3,1x,es24.16e3)', &
!> Format string for extended double precision complex numbers
FMT_COMPLEX_XDP = '(es26.18e3,1x,es26.18e3)', &
!> Format string for quadruple precision complex numbers
FMT_COMPLEX_QP = '(es44.35e4,1x,es44.35e4)'

public :: FMT_INT, FMT_REAL_SP, FMT_REAL_DP, FMT_REAL_XDP, FMT_REAL_QP
public :: FMT_COMPLEX_SP, FMT_COMPLEX_DP, FMT_COMPLEX_XDP, FMT_COMPLEX_QP

!> Version: experimental
!>
Expand Down Expand Up @@ -112,9 +127,9 @@ contains
allocate(d(nrow, ncol))
do i = 1, nrow
#:if 'real' in t1
read(s, FMT_REAL_${k1}$) d(i, :)
read(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))") d(i, :)
#:elif 'complex' in t1
read(s, FMT_COMPLEX_${k1}$) d(i, :)
read(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",1x))") d(i, :)
#:else
read(s, *) d(i, :)
#:endif
Expand Down Expand Up @@ -150,11 +165,11 @@ contains
s = open(filename, "w")
do i = 1, size(d, 1)
#:if 'real' in t1
write(s, FMT_REAL_${k1}$) d(i, :)
write(s, "(*"//FMT_REAL_${k1}$(1:len(FMT_REAL_${k1}$)-1)//",1x))") d(i, :)
#:elif 'complex' in t1
write(s, FMT_COMPLEX_${k1}$) d(i, :)
write(s, "(*"//FMT_COMPLEX_${k1}$(1:len(FMT_COMPLEX_${k1}$)-1)//",1x))") d(i, :)
#:elif 'integer' in t1
write(s, FMT_INT) d(i, :)
write(s, "(*"//FMT_INT(1:len(FMT_INT)-1)//",1x))") d(i, :)
#:else
write(s, *) d(i, :)
#:endif
Expand Down