Possible gfortran bug?

I wrote a simple StringBuffer class but the program behaves strangely. Three scenarios: it runs well, it hangs, or it produces a compiler error.

module jstringbuffer
   implicit none
   private  !# everything is private, except:

   public StringBuffer

   type :: String
      character(len=:), allocatable :: s
   end type String

   type :: StringBuffer
      integer, private :: size = 0  ! number of elems
      integer, private :: capacity = 8  ! initial capacity
      type(String), private, allocatable :: data(:)
   contains
      procedure :: append, number_of_elems, total_length, join
   end type StringBuffer

contains

   function total_length(self) result(result)
      class(StringBuffer), intent(in) :: self
      integer :: i, result

      result = 0
      do i = 1, self%size
         result = result + len(self%data(i)%s)
      end do
   end function

   function number_of_elems(self) result(result)
      class(StringBuffer), intent(in) :: self
      integer :: result
      result = self%size
   end function

   subroutine append(self, value)
      class(StringBuffer), intent(inout) :: self
      character(len=*), intent(in) :: value
      type(String), allocatable :: temp(:)

      if (self%size == 0) then
         allocate (self%data(self%capacity))
      end if
      self%size = self%size + 1
      if (self%size > self%capacity) then
         self%capacity = self%capacity * 2
         allocate (temp(self%capacity))
         temp(1:self%size - 1) = self%data(1:self%size - 1)
         call move_alloc(temp, self%data)
      end if
      self%data(self%size) = String(value)
   end subroutine

   function join(self, sep) result(result)
      class(StringBuffer), intent(in) :: self
      character(len=*), intent(in) :: sep
      character(len=:), allocatable :: result
      integer :: i, j, length, extra, len_alloc

      ! print *, sep  ! it hangs if the line "it's OK" is active

      if (.not. allocated(self%data)) then
         result = ""
      else
         extra = max(0, self%number_of_elems() - 1) * len(sep)
         len_alloc = self%total_length() + extra
         allocate (character(len=self%total_length() + extra) :: result)  ! compiler error
         ! allocate (character(len=len_alloc) :: result)  ! it's OK
         j = 1
         do i = 1, self%size
            associate (s => self%data(i)%s)
               if (i > 1) then
                  length = len(sep)
                  result(j:j + length - 1) = sep
                  j = j + length
               end if
               length = len(s)
               result(j:j + length - 1) = s
               j = j + length
            end associate
         end do
      end if
   end function

end module jstringbuffer

program alap
   use jstringbuffer
   implicit none

   type(StringBuffer) :: sb

   call sb%append("a")
   call sb%append("ccc")
   call sb%append("bb")

   print '(*(g0))', "'", sb%join(", "), "'"
end program alap

I tried it under Manjaro Linux.

$ gfortran --version
GNU Fortran (GCC) 15.2.1 20251112

In its current form, it produces a compiler error:

$ gfortran compiler_error.f90
f951: internal compiler error: Segmentation fault
0x250b271 diagnostic_context::diagnostic_impl(rich_location*, diagnostic_metadata const*, diagnostic_option_id, char const*, __va_list_tag (*) [1], diagnostic_t)
        ???:0
0x250bab0 internal_error(char const*, ...)
        ???:0
0x72ea6f gfc_find_derived_vtab(gfc_symbol*)
        ???:0
0x785452 gfc_reduce_init_expr(gfc_expr*)
        ???:0
0x753b98 gfc_match_char_spec(gfc_typespec*)
        ???:0
0x7b3e85 gfc_match_type_spec(gfc_typespec*)
        ???:0
0x7b4032 gfc_match_allocate()
        ???:0
0x81841a gfc_parse_file()
        ???:0
Please submit a full bug report, with preprocessed source (by using -freport-bug).
Please include the complete backtrace with any bug report.
See <https://gitlab.archlinux.org/archlinux/packaging/packages/gcc/-/issues> for instructions.

If you put line 68 (with “! compiler error”) in comment and uncomment the next line (“! it’s OK”), then it works fine. Now, if you uncomment line 61 (“! it hangs…”), then the program hangs until stopped with Ctrl+C.
I don’t see what the problem is here. Thanks.

1 Like

I also get a GFortran compiler error. Note that the hang is due to “printing from printing” issue with GFortran. I hit it many times as a user. When you print a result of a function, you cannot print within the function.

I also tested all combinations that you listed with LFortran and I get:

$ lfortran a.f90
'a, ccc, bb'

So I think it works, I was happy to see that. With the print in print, it shows:

$ lfortran a.f90
,
'a, ccc, bb'
1 Like

Is there a workaround to the “printing from printing” issue? During the development I’d like to see some debug info. Does writing to a file work?

Does it happen due to a limitation of the compiler?

It is a language restriction, but one that the compiler is not required to diagnose, so it is up to the programmer to avoid the situation.

The original restriction was that no i/o at all could be performed by a function in an i/o list. Somewhere along the way, the restriction was limited to i/o to the same unit. So now with a modern compiler you might avoid the problem by doing the debug output to a debug file, but you still must avoid the situation of recursive i/o to the debug file.

This particular error, which has been discussed here before, is that some of the character operations performed within character expressions (substring, concatenation) apparently use the i/o library, so the hang isn’t really caused by recursive i/o (unless I’m overlooking something in the code), but rather code that just looks like recursive i/o within the i/o library.

2 Likes

It is a recursive I/O. The last line of the main program is

 print '(*(g0))', "'", sb%join(", "), "'"

and the print statement causing the hang is inside join() function.
One can avoid the problem, without using extra debug file, by use of error_unit from the iso_fortran_env module.

module jstringbuffer
   use iso_fortran_env, only: error_unit
! [...]
   function join(self, sep) result(result)
! [...]
      write(error_unit, *) sep  ! it hangs if the line "it's OK" is active

BTW, what does child/parent data transfer statement mean in the relevant 2023 Standard section:

12.12 Restrictions on input/output statements

If a unit, or a file connected to a unit, does not have all of the properties required for the execution of certain input/output statements, those statements shall not refer to the unit.

An input/output statement that is executed while another input/output statement is being executed is a recursive input/output statement. A recursive input/output statement shall not identify an external unit that is identified by another input/output statement being executed except that a child data transfer statement may identify its parent data transfer statement external unit.

I don’t get the difference between the first part of the last sentence above (restriction) and the latter (relaxation).

2 Likes

Although less elegant, another way to solve the I/O issue, is to write in an external file.

      write(99,*) sep ; flush(99)

Thanks for the answers. And what about the compiler error? What may cause it? Those two lines do the same. Should we report this to the gfortran team? I don’t know where their issue tracker is.

I think it is here:

1 Like

Indeed, and more information about bug reporting is here:

I have a question about the recursive output here and the standard. Does the standard permit to evaluate sb%join(", ") before the print? Or is there some corner case where this would change the semantics? Most other languages, like C, C++ or Python would work like that.

I’m not sure. In C printf is a regular function, so I’d guess that all arguments (passed by values!) must be evaluated before the function is actually called. In Fortran it is a statement, so the above need not to hold. While I doubt it could pass the function to be evaluated (like here sb%join()) to the print internals (instead of that function result), it is probably allowed to somehow initiate the output before evaluating the data transfer list. After all, the restriction for the recursive I/O to the same unit must have some reasons.

1 Like

If we just want to print some debug info, we could also print to the standard error. That’s a different unit. It’s not necessary to write to a file.

2 Likes

My mistake then. That print statement within join() was commented out, and I thought the error persisted nonetheless.

The previous discussion about a program that hangs, but does not have explicit recursive i/o was here. Execute_command_line problem - #3 by RonShepard That program involved some kind odd interaction between character concatenation operations and the execute_command_line() intrinsic. I don’t think that issue was fully resolved.

I would say no. An apparent output-item may disappear altogether when it is expanded to effective items. Also, the evaluation needs to be made after preceding items have been processed. Witness:

integer:: x(10)
x = [(i,i=1,10)]
i = 2
print '(*(I0))', x(1),f(i),x(i),f(i),x(i) ! 182
contains
  function f(j) result(res)
    integer :: res(0)
    integer, intent(inout) :: j
    j = 10-j
  end function f
end program
1 Like

Thanks @themos! That did find a bug in LFortran (Fix `print '(*(I0))', x(1),f(i),x(i),f(i),x(i)` · Issue #9282 · lfortran/lfortran · GitHub). But I think you can still evaluate all these arguments before printing, in order and disappearing them as needed, but it seems you don’t need to start the actual print IO before all are evaluated. Unless there is some corner case where the output-items are interacting with the IO, but that seems prohibited by the standard.

In this example, the value of i is changed within the function f(). Is that allowed by the standard? That side effect is not allowed within an expression, but this is an i/o list, so maybe there are different rules in that case?

edit: I was curious about this case, so I did some reading in section 12 of the standard. I do think it is allowed to change the value of entities referenced in the i/o list of a write/print statement (unlike the similar situation for expressions). The list items are supposed to be evaluated in list order, so that defines the evaluation semantics.

I think the answer would be “yes”, but that evauation must be done in list order. For example, I think this code, which evaluates everything beforehand,

program xxx
   integer:: x(10), x1, x2, x3
   integer, allocatable :: f1(:), f2(:)
   x = [(i,i=1,10)]
   i = 2
   x1 = x(1)
   f1 = f(i)
   x2 = x(i)
   f2 = f(i)
   x3 = x(i)
   !print '(*(I0))', x(1),f(i),x(i),f(i),x(i) ! 182
   print '(*(I0))', x1, f2, x2, f2, x3
contains
   function f(j) result(res)
      integer :: res(1:0)
      integer, intent(inout) :: j
      j = 10-j
   end function f
end program xxx

is required to write the same output as the original version.

I was wondering how exactly that could happen. Presumably, the meaning here is that the function result, which is a zero-length array, disappears from the output list. The other interpretation is that such an array does not disappear, but its zero-length status means that nothing is transferred. There are several ways to test which interpretation is correct. One way is to use list items of different types that have type-specific output fields.

program xxx
   integer :: x(10)
   real :: a(10)
   x = [(i,i=1,10)]
   a = x
   i = 2
   print '(2i0,es0.1)', x(1),f(i),x(i),f(i),a(i)
contains
   function f(j) result(res)
      integer :: res(1:0)
      integer, intent(inout) :: j
      j = 10-j
   end function f
end program xxx

$ gfortran xxx.f90 && a.out
182.0E+0

I think this demonstrates that the zero-length list items do disappear. If they did not disappear, then there would be integer items written with the es0.1 field, which should result in an error, and also after format reversion the real item a(i) would be written in the i0 field, which should also be an error.

2 Likes

I reported the bug here. ICE confirmed.

1 Like

I was under the same impression, just going on memory. However, the standard is quite clear and a function reference that changes an actual argument (here, I), means that “that argument or any associated entities shall not appear elsewhere in the same statement” (three exceptions are listed, none apply here).

Statement, not expression, so my quoted code is invalid on that basis. Apologies!

The proximate cause of my lapse was the careful language used by the Standard in Data Transfer, General (12.6.4.5.1) :

2 All values needed to determine which entities are specified by an input/output list item are determined at the beginning of the processing of that item.
3 All values are transmitted to or from the entities specified by a list item prior to the processing of any succeeding list item for all data transfer statements.

and that is there to clarify cases where a READ statement causes a variable in the i/o list to be redefined, and that variable is referenced both before and after that variable is redefined. For PRINT or WRITE, I can’t see that issue arising.

1 Like

FYI: A bit late getting around to posting a reply, but for reference
I made a number of changes earlier trying to identify what syntax
caused the ICE and what did not, and in a good number of variants I
only saw failures when the length of the string in the ALLOCATE
was calculated using a type-bound procedure in a compound expression
,
but otherwise large changes to the types and logic had no effect. Did
not actually look at the machine code generated, just experimented with
the Fortran code. Basically the code that follows does the same thing
as the original post using INTEGER types instead of CHARACTER
types and other changes to see what effect that might have and made for
a slightly shorter reproducer. So as OP showed, calculating the length in
a separate statement appears to always provide a work-around, which might
be useful information for anyone else encountering a similar problem.

Alternate reproducer
module m_buffer
use iso_fortran_env, only: stderr=>error_unit
implicit none
type :: buffer
   integer, allocatable :: data(:)
contains
   procedure :: total_length, join
end type buffer
contains
function total_length(self) result(answer)
class(buffer),intent(in)   :: self
integer                    :: answer, szs(size(self%data))
integer,parameter          :: dp=kind(0.0d0)
   ! could just give everyone 10 spaces and trim at end
   where (self%data > 0) ! find how many characters to use for integer
      szs=int(log10(real(self%data,kind=dp)))+1
   elsewhere (self%data < 0)
      szs=int(log10(real(abs(self%data),kind=dp)))+2
   elsewhere
      szs=1
   endwhere 
   answer=sum(szs)
end function total_length
function join(self, sep) result(answer)
class(buffer), intent(in)     :: self
character(len=*), intent(in)  :: sep
character(len=:), allocatable :: answer
integer                       :: i, isz, newlen
   if (allocated(self%data)) then
      isz=size(self%data)
!#define ICE
#ifdef ICE
      ! so far only seems to fail if call type-bound procedure in an expression?
      allocate(character(len=self%total_length() + isz * len(sep)) :: answer)
#else
      newlen=self%total_length() + isz * len(sep)
      allocate(character(len=newlen) :: answer)
#endif
      write(answer,'(*(g0))')(self%data(i),sep,i=1,isz-1),self%data(isz)
      answer=answer(:len(answer)-len(sep))
   else
      answer=""
   endif
end function join
end module m_buffer
program alap
use m_buffer, only : buffer
implicit none
type(buffer) :: sb
   call info()
   sb=buffer([1,123456789,333,-789,0,huge(0)])
   print *, sb%join(", ")
   contains
subroutine info()
use, intrinsic :: iso_fortran_env, only : compiler_version
use, intrinsic :: iso_fortran_env, only : compiler_options
character(len=:),allocatable :: version, options
character(len=*),parameter   :: nl=new_line('a')
integer                      :: where, start, break
   version=compiler_version()
   options=' '//compiler_options()
   start=1
   do 
      where=index(options(start:),' -')
      if(where.eq.0)exit
      break=where+start-1
      options(break:break)=nl
      start=where
   enddo
   if(start.eq.1)then
      do 
         where=index(options(start:),' /')
         if(where.eq.0)exit
         break=where+start-1
         options(break:break)=nl
         start=where
      enddo
   endif
   print '(*(1x,a))', &
    'This file was compiled by ', &
    version,nl,        &
    'using the options ',         &
    options
end subroutine info
end program alap
 This file was compiled by  GCC version 16.0.0 20250727 (experimental) 
 using the options  
-cpp
-idirafter /usr/lib/gcc/x86_64-pc-cygwin/16/../../../../include/w32api
-idirafter /usr/lib/gcc/x86_64-pc-cygwin/16/../../../../x86_64-pc-cygwin/lib/../../include/w32api
-mtune=generic
-march=x86-64
-O0
 1, 123456789, 333, -789, 0, 2147483647

This was the reason I also thought it was allowed. That text specifies “data transfer” statements, which meant to me that the text covered also write and print statements and not just read statements. Also, it specifies the “beginning of the processing of that item” rather than the beginning of the whole write statement.

I wonder if this should be clarified officially with an interpretation?

I was also a little surprised about the idea of disappearing list items. I have determined that this applies to zero-length arrays but not to zero-length character strings. That seems like an odd incompatibility between the two similar items. For arrays, this puts a large burden on the programmer to ensure that the items in the list do not disappear so that subsequent list items match their intended format fields.

Things would be much simpler on the programmer if list items did not disappear and so that the association between the item and its format field remained fixed even if a list item has zero length. I am surprised that this has never affected me since f90 (when zero-length arrays became legal). I wonder if this issue has already been addressed in an interpretation, and, if not, should it be?