Fortran standard can definitely include better support for NAMELIST but this useful feature is not seen favorably, quite sadly in my opinion. Anyways, proposals will now have to wait for Fortran 202Y and will likely need to be very targeted, limited in scope, and clearly laid out for success, I feel. GitHub Fortran site is the best place for ideas: GitHub - j3-fortran/fortran_proposals: Proposals for the Fortran Standard Committee.
In the meantime, users with derived type needs can consider defined IO facility in the current Fortran standard even though it can get very verbose and there appear to be bugs with it in the gfortran implementation. Here’s an example I think is conforming (but I’m open to be proven wrong) and which works with a commercial compiler:
A test driver program:
use m, only : t
character(len=:), allocatable :: s
type(t) :: foo
namelist / nml_t / foo
foo = "Hello World!"
allocate( character(len=80) :: s ) ! Set the string to some suitable length
write( unit=s, nml=nml_t )
foo = ""
read( unit=s, nml=nml_t )
print *, "foo%s = ", foo%s()
end
Library code for a simple-minded ''string class" in Fortran
module m
use, intrinsic :: iso_fortran_env, only : iostat_end, iostat_eor
type :: t
private
character(len=:), allocatable :: m_s
contains
private
procedure, pass(this) :: assign_t
procedure, pass(this) :: read_t
procedure, pass(this) :: write_t
procedure, pass(this), public :: s => get_s
generic, public :: read(formatted) => read_t
generic, public :: write(formatted) => write_t
generic, public :: assignment(=) => assign_t
end type t
character(len=1), parameter :: QUOTE = '"'
character(len=1), parameter :: SLASH = '/'
character(len=1), parameter :: COMMA = ','
contains
subroutine assign_t( this, s )
class(t), intent(inout) :: this
character(len=*), intent(in) :: s
this%m_s = s
end subroutine assign_t
subroutine read_t(this, lun, iotype, vlist, iostat, iomsg)
! Argument list
class(t), intent(inout) :: this
integer, intent(in) :: lun
character(len=*), intent(in) :: iotype
integer, intent(in) :: vlist(:)
integer, intent(out) :: iostat
character(len=*),intent(inout) :: iomsg
! Local variables
character(len=:), allocatable :: s
integer, parameter :: SLEN = 10
integer :: lens
integer :: istat
logical :: begin_quote
iostat = 0
lens = 0
if (iotype == "NAMELIST") then
s = repeat( " ", ncopies=SLEN )
begin_quote = .false.
loop_read: do
lens = lens + 1
read(lun, fmt='(a1)', advance="no", iostat=istat) s(lens:lens)
select case ( istat )
case ( 0 )
select case ( s(lens:lens) )
case ( QUOTE )
if ( begin_quote ) then
lens = lens - 1
exit loop_read
else
begin_quote = .true.
s(lens:lens) = " "
end if
case ( COMMA, SLASH )
lens = lens - 1
exit loop_read
case default
end select
case ( iostat_end, iostat_eor )
exit loop_read
case default
iostat = istat
exit loop_read
end select
if ( lens == len(s) ) then
! increment length
s = s // repeat( " ", ncopies=SLEN )
end if
end do loop_read
this%m_s = trim( s(1:lens) )
end if
! elided are the instructions for other IOTYPE values
return
end subroutine read_t
subroutine write_t(this, lun, iotype, vlist, istat, imsg)
! Argument list
class(t), intent(in) :: this
integer, intent(in) :: lun
character(len=*), intent(in) :: iotype
integer, intent(in) :: vlist(:)
integer, intent(out) :: istat
character(len=*),intent(inout) :: imsg
if (iotype == "NAMELIST") then
write(lun, fmt="(g0)", iostat=istat, iomsg=imsg) QUOTE // trim(this%m_s) // QUOTE
end if
! elided are the instructions for other IOTYPE values
return
end subroutine write_t
function get_s( this ) result( s )
class(t), intent(in) :: this
character(len=:), allocatable :: s
if ( allocated(this%m_s) ) then
s = this%m_s
else
s = ""
end if
end function
end module
Execution of program built with a commercial compiler gives me the expected output:
foo%s = Hello World!