Error help: Unexpected element '<' in format string

Hi all:

I am trying to compile an older version of Fortran code (likely not for gfortran compiler), and it seems that the formatting syntax has changed in gfortran.

For the following line of code,
write(ch,'(<mypar%l>f12.4)') (mypar%mu(ii,jj,tt), jj=1,mypar%l)

I have got the following error.
Error: Unexpected element '<' in format string

I am writing to see if there is any quick fix to this issue.

Thanks, and I look forward to hearing from you!

Best,
Long

Why not just replace < and > in the format string with "?

This was an old vax extension. It is nonstandard, and I don’t think it is supported by any modern compilers.

Try '(*(f12.4))', and see if that works.

Quoting Dr. Fortran:

Variable Format Expressions (VFEs) [were] created by DEC in the 1970s and it earned the enmity of Fortran compiler writers everywhere who were pestered by their customers to support it as well. With VFEs, you can enclose an integer expression in angle brackets and the value of the expression will be used in the format. For example:

write (30, '(<n>(2x,f8.2)') array

Intel Fortran, of course, given its DEC heritage, supports VFEs, but I don’t recommend their use if you have other reasonable options.

Look to the future

Fortran 2008 solves this problem with a feature called the “unlimited format item” where a * can be used as a group repeat count. Its effect is “as if its enclosed list were preceded by a very large repeat count”. For example:

'(*(2x,f8.2))'

This lets you avoid having to write a specific large number as the repeat count and makes it more obvious what is going on.

1 Like

Still supported by several compilers. ifort/ifx has the extension, called the “VFE” extension.
For compilers that do not, you can convert it to an internal write relatively easily. Looks like
@Beliavsky got to that already. A little example is

program extension
! use Variable Format Expression (VFE) extension
implicit none
integer :: int1, int2, iostat
character(len=256) :: iomsg
character(len=256) :: fmt
   int1=3
   int2=1

! USE EXTENSION
   write(*,101,iostat=iostat,iomsg=iomsg)10,20,30
! <int2> is replaced by it's value, same for <int1>
101 format(<int2>(:"[",i0,"]"),<int1>(:"[",i0,"]"))
   if(iostat.ne.0)write(*,*)trim(iomsg)

! USE STANDARD INTERNAL WRITE TO CREATE FORMAT
write(fmt,'(*(g0))')'(',int2,'(:"[",i0,"]")',int1,'(:"[",i0,"]")',')'
! so you can see what that did
write(*,*)'CREATED FORMAT STATEMENT:',trim(fmt)
   write(*,fmt,iostat=iostat,iomsg=iomsg)10,20,30
   if(iostat.ne.0)write(*,*)trim(iomsg)

end program extension

So for complicated formats where you actually need to generate the format the VFE would; use
internal writes to build a normal format and use that as a standard way to do the equivalent. For a lot of simple statements any of the above suggestions can help. For the simple one you posted an “exact” equivalent would be

VFE: block
character(len=256) :: fmt  
! this would build the format
write(fmt,'(*(g0))')'(', mypar%l, 'f12.4)'
! show the format for fun
write(*,*)'fmt=',trim(fmt)
! use the format
write(ch,fmt) (mypar%mu(ii,jj,tt), jj=1,mypar%l)
endblock VFE

Thank you so much everyone, especially @Beliavsky for sharing the insightful notes! The problem is fixed!