Ifort namelist bug?

The Fortran program below happily compiles and runs with gfortran; ifort complains at run time with

forrtl: severe (17): syntax error in NAMELIST input, unit -5, file Internal Formatted NML Read, line -1, position 38

Position 38 of list is its last nonblank character. I suspect the problem may be related to one that I had some years ago with internal list-directed writing huge(1d0) then list-directed reading the result. My test program:

program nmltest3
  implicit none
  integer,parameter:: dp = selected_real_kind(15)
  real(dp):: dpx = huge(dpx)
  character:: list*80
  namelist /dpstuff/ dpx
  write(list,nml=dpstuff)
  print *,'After writing dpstuff, list is ',trim(list)
  print *,'len_trim(list) is ',len_trim(list)
  read(list,nml=dpstuff)  
  print *,'After reading dpstuff dpx is',dpx
end program nmltest3

If I change 15 to 33 in that program then ifort and gfortran are both happy with it. Is it standard-conforming?

The default rounding mode is probably writing a value larger than huge(0.0d0); which it cannot then read back in. Try adding “ROUND=‘DOWN’” on the WRITE to LIST. The default is up to the compiler. Because of the “friendly” way ifort/ifx writes list-directed and NAMELIST output which usually gives a representation closer to what a human expects this edge condition shows up now and then. If you just do a “write(,)huge(0.0d0)” with various compilers, and maybe play with adding ROUND=“{UP,DOWN,ZERO,NEAREST, …}” you can see various compilers can write a value they cannot read back in, and that it is common for the number of digits and the value of the last digit or two to vary with NAMELIST group and list-directed (ie. “*”)’ output. So I guess you could say it is a standard-conforming failure. I almost always set the delimiter and round mode on NAMELIST output for portability, as you can write CHARACTER strings you cannot read back in pretty easily. as well if you do not require a delimiter on the WRITE.

I did not check, but there is a slight chance the standard says that anything written as a NAMELIST group has to be able to be read back in as a NAMELIST group in a totally portable manner, given that NAMELIST files are basically used to transfer data between programs.
But given the long-standing issue with string delimiters I really do not think so.

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

The standard does not say this - as you surmise, string delimiters are an issue. There is a note:

Namelist output records produced with a DELIM= specifier with a value of NONE and which contain a character sequence might not be acceptable as namelist input records.

Many thanks to urbanjost and sblionel. I had thought of a workaround for the ifort problem with huge(1d0) in a namelist by using nearest(huge(1d0),-1d0) instead, and multiplying the result by huge(1d0)/nearest(1d0,-1d0) afterwards. That revealed a bug in gfortran, which I reported, and I’m glad to say the gfortran people are working on fixing it. The bug was that nearest(huge(1d0),-1d0) gave huge(1d0)/2 instead of the correct value, which according to both ifort and g95 is
huge(1d0)*(1-epsilon(1d0)/2). I also tried real32, real80 (“extended precision”) and real128. Gfortran had the same bug in all of them, and ifort was correct, though it does not support 80-bit precision.

My original problem would have been avoided if ifort had used one more significant digit in list-directed output of very large real64 numbers than at present, but I suspect that Intel won’t do that because it would give more output that looked incorrect in its last digit or two to users who don’t understand the oddities of floating-point arithmetic.