Type, allocation of, and assignment to deferred-length character arrays

Dear all,

I’m trying to use a modified version of an old fortran program (I believe at first it was written in fortran 77 or older), on linux (Fedora 40, x86_64).

The program works fine when compiled using Intel ifx/ifort 2024.2, but does NOT when compiled with gfortran 14.2.1 20240912 (Red Hat 14.2.1-3).

The program uses deferred-length arrays of real, integer and character. Inspecting with a debugger (gdb), it seems to me that the allocation of, or the assignment to the deferred-length character arrays do not work when compiled with gfortran (deferred-length integer/real arrays work properly):

  • ptypeing returns
    type = Type 
    End Type 
    
  • elements of the array are emtpy after assignments.

Compiled using ifort, ptype on the same character array returns, say, type = character*6, allocatable (8,3) or something like that.

The attached program (defchararr.f90) and module (arraymod.f90) contains the essence of the corresponding routines in the failed program (although these are embedded several layers below the main routine). Strange enough, when the attached program is compiled using gfortran, the assignment works OK (and prints “ahoaho”) although ptypeing over the array shows nothing (the same as above, that is, type = Type and End Type (with ifx/ifort, ptype returns type = character*6, allocatable (8,3) and it also prints “ahoaho”).

Could someone suggest me what’s wrong with the failed program and how I can fix it? Are there any restrictions on the use of the deferred-length character arrays? (I’m an old-time fortran (77) user and the knowledge on the modern standards is very limited…)

As I’m new to this discourse group I can not upload files, I’ll show the contents of defchararr.f90 below.

Thanks in advance.
Kazuyoshi

defchararr.f90:

program defchararr
  use arraymod
  character*6 aho
  call aloc_arr(3)
  chararr(1,1)=aho()
  print *, chararr(1,1)
end program defchararr

character*6 function aho()
  aho="ahoaho"
  return
end function aho

arraymod.f90:

module arraymod
  parameter(num=8)
  character(len=:), allocatable :: chararr(:,:)
contains
  subroutine aloc_arr(nregs)
    allocate(character(len=6) :: chararr(num,nregs))
  end subroutine aloc_arr
end module arraymod

So the reproducer program has no problem accept it does not produce what you expect in the debugger, or is the reproducer failing in some way? Because you were using the debugger and saw the type not returning you may have identified a bug in the debugger/compiler interface and
not the cause of your program bug if that is the case.

I see nothing wrong with the reproducer myself. It has a few oddities but given the age and that it is a reduced example that is understandable.

But if the example program itself is not working I could not reproduce a problem with it. So what compiler options are you using? I would recommend putting the AHO() function in a module or making it a contained procedure.

I would recommend adding an EXTERNAL statement to see if that has any effect. It makes it clearer AHO is a procedure without an explicit interface as well.

At the moment I do not have gdb available but I will later but in the meantime does this
replacement for the main program print the expected results, and if you make AHO() a contained
procedure does anything improve?

program defchararr
use arraymod, only : aloc_arr, chararr
implicit none
character*6 aho
external aho
   call aloc_arr(3)
   chararr(1,1)=aho()
   print *, chararr(1,1)
   call whatami(chararr(1,1))
   call whatami(aho())
contains
subroutine whatami(a)
class(*),intent(in) :: a
   select type ( a  )
   type is ( integer )
      write(*,'(*(g0:,1x))')'type is integer, kind=',kind(a)
   type is ( character(len=*) )
      write(*,'(*(g0:,1x))')'type is character, len=',len(a)
   class default
      write(*,'(*(g0:,1x))')'sorry, I do not know your type'
   end select
end subroutine whatami
end program defchararr

Expected

 ahoaho
type is character, len= 6
type is character, len= 6

@urbanjost , thanks for your comments.

No problem in the reproducer program, except that ptypeing in the debugger shows nothing (type = Type and then End Type).

This replacement, with the aho() function separated into independent object and the original arraymod.o, shows the expected result, though the ptype of chararr() is empty! This probably indicates that there’s an issue in the debugger/compiler interface, right? (though it may not lead to resolve the issue of substitution into deferred-length character arrays in the old program).

Ah, I forgot to mention the compiler option; nothing for the reproducer, and -O -I$(INCDIR) for the original (and -g for debugging).

Kazuyoshi

It is hard to say; but there is a reasonable possibility what you are seeing is a problem with the debugger interface. It could be a hint that there is a related problem as well, so it is not definitive to me, and it could be misleading you. I would compile with all the debug flags on that you see and see if something else is flagged. There are problems with gfortran and character functions. If you are using a call to aho() as an argument in another call try passing aho()//‘’ instead of just aho() ; but otherwise you need to create a reproducer that produces the problem outside of the debugger, or provide more info on what you are seeing that is wrong in the actual program to make this easier for the rest of us to look at, I think.