Well, using your example and using ROUND=‘DOWN’ does prevent the error; the output is interesting with each compiler I tried so far.
program nmltest3
implicit none
integer, parameter :: dp = selected_real_kind(15)
real(dp) :: dpx
character :: list*80, iomsg*256
integer :: iostat, i
character(len=*),parameter:: all='(*(g0,1x))'
character(len=*), parameter :: rounds(*) = [character(len=20) :: &
& 'UP', 'DOWN', 'ZERO', 'NEAREST', 'COMPATIBLE', 'PROCESSOR_DEFINED']
namelist /dpstuff/ dpx
print *, 'list-directed dpx is', huge(dpx)
do i = 1, size(rounds)
print all, repeat('-', 80)
dpx = huge(dpx)
write (*, '(a,g80.70,1x)', ROUND=rounds(i)) rounds(i), dpx
write (list, nml=dpstuff, round=rounds(i))
print all, rounds(i), ' list is ', trim(list)
read (list, nml=dpstuff, iostat=iostat, iomsg=iomsg)
if (iostat /= 0) then
write (*, all) trim(iomsg)
else
print all, 'After reading dpstuff dpx is', dpx
end if
end do
end program nmltest3
list-directed dpx is 1.797693134862316E+308
--------------------------------------------------------------------------------
UP 0.1797693134862315708145274237317043567990000000000000000000000000000000+309
UP list is &DPSTUFF DPX= 1.797693134862316E+308/
syntax error in NAMELIST input, unit -5, file Internal Formatted NML Read, line -1, position 38
--------------------------------------------------------------------------------
DOWN 0.1797693134862315708145274237317043567980000000000000000000000000000000+309
DOWN list is &DPSTUFF DPX= 1.797693134862315E+308/
After reading dpstuff dpx is .1797693134862315E+309
--------------------------------------------------------------------------------
ZERO 0.1797693134862315708145274237317043567980000000000000000000000000000000+309
ZERO list is &DPSTUFF DPX= 1.797693134862315E+308/
After reading dpstuff dpx is .1797693134862315E+309
--------------------------------------------------------------------------------
NEAREST 0.1797693134862315708145274237317043567980000000000000000000000000000000+309
NEAREST list is &DPSTUFF DPX= 1.797693134862316E+308/
syntax error in NAMELIST input, unit -5, file Internal Formatted NML Read, line -1, position 38
--------------------------------------------------------------------------------
COMPATIBLE 0.1797693134862315708145274237317043567980000000000000000000000000000000+309
COMPATIBLE list is &DPSTUFF DPX= 1.797693134862316E+308/
syntax error in NAMELIST input, unit -5, file Internal Formatted NML Read, line -1, position 38
--------------------------------------------------------------------------------
PROCESSOR_DEFINED 0.1797693134862315708145274237317043567980000000000000000000000000000000+309
PROCESSOR_DEFINED list is &DPSTUFF DPX= 1.797693134862316E+308/
syntax error in NAMELIST input, unit -5, file Internal Formatted NML Read, line -1, position 38