Catastrophic Compile error on ifx when defining a pointer to a "long" function name

We recently renamed a few variables in the DAMASK repository, which now generates the error

catastrophic error: **Internal compiler error: Creating this name exceeds internal buffer: grid_mechanical_spectral_polarization_mp_grid_mechanical_spectral_polarization_solution__templ_10

when compiling with ifx, version 2022.0.1 oneapi. While it is a long function name, we don’t think it warrants a compile error like this.

@greenrongreen is it enough to create a topic here, or should we submit a proper bug-report to intel?

@MarDie

It should not cause an ICE. I will dig into this.

Due to the age of our compiler, our symbol table has a limit of 92 characters for a symbol name.
This was adequate for F90, but obviously too small today. The trouble is that the symbol table is used throughout the code. So if we increase it we will probably break the compiler in many many places.
This is 92 characters for the decorated name, not the variable name. The decorated name includes
<module name>_mp_<variable name>_
where “_mp_” glues together the module name and the module variable (or function) name for the symbol name. There is a trailing underscore appended as well. This name is what is entered into the compilers symbol table.
Having a symbol table of limited characters obviously does not conform to modern Fortran Standards name lengths. It is unfortunate and leads to issues like this one.
We have discussed changing this old limit. But imagine, every single place the symbol table is referenced is a possible breakage. it’s a major refactoring. I’ll bring this up with the team and looke at our committed features and other work for the coming updates and major releases. This would be one we’d have to do right after a code freeze and before the next one.

2 Likes

Since the module name and the variable name should be supported up to a length of 63 each and additional characters are added as well 92 is certainly a problem; but 63 is the limit defined in the standard for a variable name last I knew; so you should not get an ICE
but anything over 63 characters is non-standard so the name would generate an error in most compilers anyway. Some might allow it as an extension, of course… So it is non-standard regardless of what additional problems might be incurred with internal representations with a particular compiler.

It is good to know I had best keep module names short when using ifx/ifort.

92-63-5=24; So I think I am hearing that if I want variables up to 63 characters long I should keep module names to 24 instead of the standard 63?

11      6.2.2   Names
12      Names are used for various entities such as variables, program units, dummy arguments, named constants, and
13      nonintrinsic types.
14      R603   name                      is  letter [ alphanumeric-character ] ...
15      C601   (R603) The maximum length of a name is 63 characters.
        NOTE1
        Examples of names:
          A1
          NAME_LENGTH           (single underscore)
          S_P_R_E_A_D__O_U_T    (two consecutive underscores)
          TRAILER_              (trailing underscore)

A sample program that indicates if arguments passed to the command are valid Fortran names

program fortran_symbol_name
implicit none
integer                      :: count, i, argument_length, istat
character(len=:),allocatable :: arg
   count = command_argument_count()
   do i=1,count
      call get_command_argument(number=i,length=argument_length)
      if(allocated(arg))deallocate(arg)
      allocate(character(len=argument_length) :: arg)
      call get_command_argument(i, arg,status=istat)
      if(istat.eq.0)then
         write(*,'(*(g0,1x))')fortran_name(arg),arg
      endif
   enddo
contains
elemental function fortran_name(line) result (lout)
! determine if a string is a valid Fortran name
! ignoring trailing spaces (but not leading spaces)
character(len=*),parameter ::         &
& int='0123456789',                   &
& lower='abcdefghijklmnopqrstuvwxyz', &
& upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ', &
& allowed=upper//lower//int//'_'

character(len=*),intent(in)  :: line
character(len=:),allocatable :: name
logical                      :: lout
   name=trim(line)
   if(len(name).ne.0)then
      ! first character is alphameric
      lout = verify(name(1:1), lower//upper) == 0  &
       ! other characters are allowed in a symbol name
       & .and. verify(name,allowed) == 0           &
       ! allowable length
       & .and. len(name) <= 63
   else
      lout = .false.
   endif
end function fortran_name
end program fortran_symbol_name

Thanks for the explanation

Unfortunately, it is not as easy as that. Have a look at “Global name too long” with an example of how ifort/ifx blows up names. If submodules (and contained procedures, blocks(?) etc) are involved length of names easily go overboard.
For larger (sub)module based projects due to the global namespace of fortran this has become a nuisance.

An idea for the compiler developers could be to create a hash of <module name>_mp_<variable name>_, since it will certainly be shorter than 92 characters. Then of course you’ll need to store the list of hashes so that we can get nice log messages when the program crashes.

The term catastrophic seems quite strong to me. When I read the title from this post I thought the ifx error destroyed a computer cluster or something like that. :slight_smile: But it looks like as “just” an internal compiler error.