public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
@ 2023-11-06 15:26 trnka at scm dot com
  2023-11-06 15:27 ` [Bug fortran/112407] " trnka at scm dot com
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: trnka at scm dot com @ 2023-11-06 15:26 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

            Bug ID: 112407
           Summary: [13 Regression] Fix for PR37336 triggers an ICE in
                    gfc_format_decoder while constructing a vtab
           Product: gcc
           Version: 13.2.1
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: trnka at scm dot com
  Target Milestone: ---

Created attachment 56515
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56515&action=edit
reproducer with dependencies

Following up on comment 7 in PR109684. This seems to be another issue uncovered
by the finalization overhaul:

commit r13-6747-gd7caf313525a46f200d7f5db1ba893f853774aee
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Sat Mar 18 07:56:23 2023 +0000

    Fortran: Fix bugs and missing features in finalization [PR37336]

    2023-03-18  Paul Thomas  <pault@gcc.gnu.org>

The attached test triggers an assert in gfc_format_decoder, at
fortran/error.cc:1078 (on current 13 branch):

0x65cce5 gfc_format_decoder
        gcc/fortran/error.cc:1078
0x1b12ed9 pp_format(pretty_printer*, text_info*)
        gcc/pretty-print.cc:1475
0x1b030d1 diagnostic_report_diagnostic(diagnostic_context*, diagnostic_info*)
        gcc/diagnostic.cc:1592
0x6e0127 gfc_report_diagnostic
        gcc/fortran/error.cc:890
0x6e0127 gfc_warning
        gcc/fortran/error.cc:923
0x6e07e6 gfc_warning(int, char const*, ...)
        gcc/fortran/error.cc:954
0x765d5e resolve_procedure_expression
        gcc/fortran/resolve.cc:1956
0x765d5e resolve_variable
        gcc/fortran/resolve.cc:6066
0x765d5e gfc_resolve_expr(gfc_expr*)
        gcc/fortran/resolve.cc:7302
0x7635c9 gfc_resolve_expr(gfc_expr*)
        gcc/fortran/resolve.cc:7267
0x7635c9 resolve_structure_cons
        gcc/fortran/resolve.cc:1341
0x774521 resolve_values
        gcc/fortran/resolve.cc:12802
0x78afd2 do_traverse_symtree
        gcc/fortran/symbol.cc:4190
0x76ac7d resolve_types
        gcc/fortran/resolve.cc:17941
0x771efc gfc_resolve(gfc_namespace*)
        gcc/fortran/resolve.cc:18038
0x760d1e resolve_symbol
        gcc/fortran/resolve.cc:16602
0x78afd2 do_traverse_symtree
        gcc/fortran/symbol.cc:4190
0x76ab9e resolve_types
        gcc/fortran/resolve.cc:17920
0x771efc gfc_resolve(gfc_namespace*)
        gcc/fortran/resolve.cc:18038
0x760d1e resolve_symbol
        gcc/fortran/resolve.cc:16602

This assert is hit while printing the following warning:

#0  gfc_warning (opt=0,
    gmsgid=0x1e55748 "Non-RECURSIVE procedure %qs at %L is possibly calling
itself recursively.  Declare it RECURSIVE or use %<-frecursive%>")

In particular, the following line in gfc_format_decoder is failing:

gcc_assert (loc->nextc - loc->lb->line >= 0);

That's because both loc->nextc and loc->lb are 0 here. Walking up the stack, I
have found that this all happens while resolving the structure constructor for
__vtab_ftldynarrayintmodule_Ftldynarrayint. cons->where and cons->expr->where
in resolve_structure_cons both look like the bogus locus causing the assert:

(gdb) p cons->where
$6 = {nextc = 0x0, lb = 0x0}
(gdb) p cons->expr->where
$8 = {nextc = 0x0, lb = 0x0}

Picking the massive commit mentioned above apart into small chunks and
reverting them one by one, I have narrowed the triggering change down to the
following addition to resolve_symbol():

  if (!sym->attr.referenced
      && (sym->ts.type == BT_CLASS || sym->ts.type == BT_DERIVED))
    {
      gfc_expr *final_expr = gfc_lval_expr_from_sym (sym);
      if (gfc_is_finalizable (final_expr->ts.u.derived, NULL))
       gfc_set_sym_referenced (sym);
      gfc_free_expr (final_expr);
    }

Specifically, it's the call to gfc_find_derived_vtab() in gfc_is_finalizable()
on the affected module that directly triggers the bug. Two TBPs in the affected
type are directly involved in triggering the assert. Applying the attached hack
works around the issue (by skipping the call to gfc_find_derived_vtab() for the
two affected routines.

FWIW, both affected routines (NewCopyOther and AssignOther) have two arguments
like this:

   subroutine NewCopyOther(self, other)
      class(ftlDynArrayInt), intent(out) :: self
      type(ftlDynArrayInt),  intent(in)  :: other

   impure elemental subroutine AssignOther(self, other)
      class(ftlDynArrayInt), intent(inout) :: self
      type(ftlDynArrayInt),  intent(in)    :: other

It's always the "other" argument which triggers this, the "self" one never hits
the bit in resolve_symbol() mentioned above. Changing "other" to
class(ftlDynArrayInt) also makes the issue go away.

To reproduce this, unpack the attached tarball (containing the testcase and
three dependency .mod files) and run gfortran -c test-vtab-construct-ice.f90.
The ftlDynArrayInt type hitting the issue is pulled in by the
ChemicalSystemModule, which seems to be a key ingredient. It's a really big
module with dozens of dependencies (so I can't feasibly provide them all) and
the chemicalsystemmodule.mod is about a megabyte uncompressed. It looks like
the bug depends on the size/layout of this big module, because I wasn't able to
reduce it without making the issue go away. However, while removing any
component from the ChemicalSystemType made the issue disappear, stuffing the
type with a few integer components then made the issue come back again.

It also doesn't seem to be possible to reduce test-vtab-construct-ice.f90
further. Even the order of the subroutines seems to matter, putting A() last
makes the issue go away.

I'm happy to assist with debugging this, although I can't provide the sources
for all the modules involved as this involves a significant part of our
proprietary codebase. If you can help me narrow down the cause a bit, perhaps
we can then design a synthetic testcase that could then be included in the GCC
regression test suite.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
@ 2023-11-06 15:27 ` trnka at scm dot com
  2023-11-07  8:34 ` [Bug fortran/112407] [13/14 " rguenth at gcc dot gnu.org
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: trnka at scm dot com @ 2023-11-06 15:27 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #1 from Tomáš Trnka <trnka at scm dot com> ---
Created attachment 56516
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56516&action=edit
Hacky patch working around the issue on this testcase

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
  2023-11-06 15:27 ` [Bug fortran/112407] " trnka at scm dot com
@ 2023-11-07  8:34 ` rguenth at gcc dot gnu.org
  2023-11-07 14:25 ` pault at gcc dot gnu.org
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: rguenth at gcc dot gnu.org @ 2023-11-07  8:34 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Richard Biener <rguenth at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4
   Target Milestone|---                         |13.3
            Summary|[13 Regression] Fix for     |[13/14 Regression] Fix for
                   |PR37336 triggers an ICE in  |PR37336 triggers an ICE in
                   |gfc_format_decoder while    |gfc_format_decoder while
                   |constructing a vtab         |constructing a vtab
           Keywords|                            |ice-on-valid-code

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
  2023-11-06 15:27 ` [Bug fortran/112407] " trnka at scm dot com
  2023-11-07  8:34 ` [Bug fortran/112407] [13/14 " rguenth at gcc dot gnu.org
@ 2023-11-07 14:25 ` pault at gcc dot gnu.org
  2023-11-07 16:04 ` trnka at scm dot com
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2023-11-07 14:25 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2023-11-07
     Ever confirmed|0                           |1

--- Comment #2 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Tomáš Trnka from comment #1)
> Created attachment 56516 [details]
> Hacky patch working around the issue on this testcase

Hi Tomáš,

'newcopyother' is determined to be recursive. The ICE arises because the line
buffer field, lb, of the expression locus is NULL (where = {nextc = 0x0, lb =
0x0}).

Compiling with -frecursive fixes the ICE in the testcase. Does that permit the
build to proceed?

This fixes the problem and is regression testing as I write.

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 81a14653a04..192a9c74b41 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -1969,6 +1969,10 @@ resolve_procedure_expression (gfc_expr* expr)
       || (sym->attr.function && sym->result == sym))
     return true;

+  /* Do not test "hidden" module symbols for recursion.  */
+  if (sym->attr.use_assoc && expr->symtree->name[0] == '@')
+    return true;
+
   /* A non-RECURSIVE procedure that is used as procedure expression within its
      own body is in danger of being called recursively.  */
   if (is_illegal_recursion (sym, gfc_current_ns))

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (2 preceding siblings ...)
  2023-11-07 14:25 ` pault at gcc dot gnu.org
@ 2023-11-07 16:04 ` trnka at scm dot com
  2023-11-08 10:51 ` pault at gcc dot gnu.org
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: trnka at scm dot com @ 2023-11-07 16:04 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #3 from Tomáš Trnka <trnka at scm dot com> ---
Yes, -frecursive makes the build pass and it is a workaround which I have been
using ever since upgrading to 13. Should have mentioned that, sorry.

I see that something is making the compiler think the routine is recursive,
even though it very clearly is not. The full original source of that module is
available from
https://github.com/SCM-NV/ftl/blob/master/src/ftlDynArray.F90_template, but
even if I make the two affected routines (NewCopyOther and AssignOther)
completely empty, the issue persists:

   subroutine NewCopyOther(self, other)
      class(CAT(ftlDynArray,FTL_TEMPLATE_TYPE_NAME)), intent(out) :: self
       type(CAT(ftlDynArray,FTL_TEMPLATE_TYPE_NAME)), intent(in)  :: other

   end subroutine

   impure elemental subroutine AssignOther(self, other)
      class(CAT(ftlDynArray,FTL_TEMPLATE_TYPE_NAME)), intent(inout) :: self
       type(CAT(ftlDynArray,FTL_TEMPLATE_TYPE_NAME)), intent(in)    :: other

   end subroutine

So it looks like the compiler got confused for some reason. That's why I don't
feel just using -frecursive is a valid long-term solution, because it feels
like purely masking the symptoms but who knows what else is affected by the
confusion.

I'll test the patch shortly.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (3 preceding siblings ...)
  2023-11-07 16:04 ` trnka at scm dot com
@ 2023-11-08 10:51 ` pault at gcc dot gnu.org
  2023-11-08 15:32 ` trnka at scm dot com
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2023-11-08 10:51 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Assignee|unassigned at gcc dot gnu.org      |pault at gcc dot gnu.org

--- Comment #4 from Paul Thomas <pault at gcc dot gnu.org> ---
Created attachment 56531
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56531&action=edit
Fix for this PR

The bug comes about because the vtable is being declared in one of the specific
procedures typebound to the derived type, thereby making the procedure
implicitly recursive. The attached fix gives this specific procedure the
recursive attribute.

The patch regression tests OK.

I have yet to understand why the vtable is not being declared in the containing
module namespace. I'll dig around some more after I have done some paid work
:-)

Perhaps you could try a build with this patch and -frecursive removed.

Paul

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (4 preceding siblings ...)
  2023-11-08 10:51 ` pault at gcc dot gnu.org
@ 2023-11-08 15:32 ` trnka at scm dot com
  2023-11-09 14:03 ` pault at gcc dot gnu.org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: trnka at scm dot com @ 2023-11-08 15:32 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #5 from Tomáš Trnka <trnka at scm dot com> ---
(In reply to Paul Thomas from comment #4)
> Created attachment 56531 [details]
> Fix for this PR
> 
> The bug comes about because the vtable is being declared in one of the
> specific procedures typebound to the derived type, thereby making the
> procedure implicitly recursive. The attached fix gives this specific
> procedure the recursive attribute.

This fix seems to work great, all of our stuff builds and passes tests without
any new trouble (without -frecursive). Your previous patch in comment 2 also
seems to work (our code builds fine, but I haven't tested that variant
thoroughly).

I'm looking forward to any more information on the root cause.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (5 preceding siblings ...)
  2023-11-08 15:32 ` trnka at scm dot com
@ 2023-11-09 14:03 ` pault at gcc dot gnu.org
  2024-03-29  7:57 ` pault at gcc dot gnu.org
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2023-11-09 14:03 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #6 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Tomáš Trnka from comment #5)

> I'm looking forward to any more information on the root cause.

I have failed to produce a compact reproducer that resembles your bug. In fact,
you will note the first comment in the reproducer below, which is a bit ironic
:-).

You will note the commented out assignment and select type block. These
generate the exact error. ie. Whenever 'new_t' appears in a variable expression
the error is triggered.

I am deeply puzzled and will have another go at achieving some enlightenment
tomorrow.

Paul

module m
  private new_t

  type s
    procedure(),pointer,nopass :: op
  end type

  type :: t
    integer :: i
    type (s) :: s
  contains
    procedure :: new_t
    procedure :: bar
    procedure :: add_t
    generic :: new => new_t, bar
    generic, public :: assignment(=) => add_t
    final :: final_t
  end type

  integer :: i = 0, finals = 0

contains
!  recursive subroutine new_t (arg1, arg2) ! gfortran doesn't detect the
recursion
  subroutine new_t (arg1, arg2)            ! in 'new_t'! Other brands do.
    class(t), intent(out) :: arg1
    type(t), intent(in)  :: arg2
    i = i + 1
!    arg1%s%op => new_t          ! This generates the error

!    select type (arg1)          ! As does this
!      type is (t)
!        arg1 = t(arg1%i,s(new_t))
!    end select

    print *, "new_t"
    if (i .ge. 10) return

!    arg1 = arg2                 ! gfortran does not detect the recursion

    if (arg1%i .ne. arg2%i) then ! According to F2018(8.5.10), arg1 should be
      arg1%i = arg2%i            ! undefined on invocation, unless any
sub-components
      call arg1%new(arg2)        ! are default initialised. gfortran sets
arg1%i = 0
    endif                        ! gfortran misses this recursion
  end

  subroutine bar(arg)
    class(t), intent(out) :: arg
    call arg%new(t(42, s(new_t)))
  end

  subroutine add_t (arg1, arg2)
    class(t), intent(out) :: arg1
    type(t), intent(in)  :: arg2
    call arg1%new (arg2)
  end

  impure elemental subroutine final_t (arg1)
    type(t), intent(in) :: arg1
    finals = finals + 1
  end
end

  use m
  class(t), allocatable :: x
  allocate(x)
  call x%new()                   ! gfortran ouputs 10*'new_t'
  print *, x%i, i, finals        !        -||-     0 10 11
!
! The other brands output 2*'new_t' + 42 2 3
end

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (6 preceding siblings ...)
  2023-11-09 14:03 ` pault at gcc dot gnu.org
@ 2024-03-29  7:57 ` pault at gcc dot gnu.org
  2024-03-29 14:10 ` pault at gcc dot gnu.org
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2024-03-29  7:57 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #7 from Paul Thomas <pault at gcc dot gnu.org> ---
Created attachment 57833
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57833&action=edit
A patch that fixes all the issues in this PR

I apologise for taking so long to return to this problem. Daytime work and a
long trip to Australia have removed my gaze from the ball.

At this stage of the release cycle, I have decided to go for the safe, "hacky"
fix of your problem.

In the course of the investigation, I found that recursion involving type bound
procedures was not being detected and that class objects with NULL default
initializers were being applied to intent(OUT) dummies. These are both fixed.

I will submit to the list as soon as I have written the ChangeLogs.

Regards

Paul

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (7 preceding siblings ...)
  2024-03-29  7:57 ` pault at gcc dot gnu.org
@ 2024-03-29 14:10 ` pault at gcc dot gnu.org
  2024-03-30  7:27 ` pault at gcc dot gnu.org
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2024-03-29 14:10 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #8 from Paul Thomas <pault at gcc dot gnu.org> ---
Created attachment 57835
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57835&action=edit
An alternative fix for the PR

Hi Tomas,

Would you prefer the compiler to give warning rather than letting the possible
recursion to pass by silently?

f951: Warning: Non-RECURSIVE procedure ‘newcopyother’ from module
‘ftldynarrayintmodule’ is  possibly calling itself recursively in procedure
‘newcopyother’.  Declare it RECURSIVE or use ‘-frecursive’

Cheers

Paul

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (8 preceding siblings ...)
  2024-03-29 14:10 ` pault at gcc dot gnu.org
@ 2024-03-30  7:27 ` pault at gcc dot gnu.org
  2024-04-02 13:19 ` cvs-commit at gcc dot gnu.org
  2024-04-23  9:45 ` [Bug fortran/112407] [13 " pault at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2024-03-30  7:27 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #9 from Paul Thomas <pault at gcc dot gnu.org> ---
(In reply to Paul Thomas from comment #8)
> Created attachment 57835 [details]
> An alternative fix for the PR
> 
> Hi Tomas,
> 
> Would you prefer the compiler to give warning rather than letting the
> possible recursion to pass by silently?
> 
> f951: Warning: Non-RECURSIVE procedure ‘newcopyother’ from module
> ‘ftldynarrayintmodule’ is  possibly calling itself recursively in procedure
> ‘newcopyother’.  Declare it RECURSIVE or use ‘-frecursive’
> 
> Cheers
> 
> Paul

After reflection, I have answered the question myself. The other part of the
patch in resolve.cc should ensure that the recursion is detected in the module
compilation.

Paul

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (9 preceding siblings ...)
  2024-03-30  7:27 ` pault at gcc dot gnu.org
@ 2024-04-02 13:19 ` cvs-commit at gcc dot gnu.org
  2024-04-23  9:45 ` [Bug fortran/112407] [13 " pault at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2024-04-02 13:19 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #10 from GCC Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Paul Thomas <pault@gcc.gnu.org>:

https://gcc.gnu.org/g:35408b3669fac104cd380582b32e32c64a603d8b

commit r14-9752-g35408b3669fac104cd380582b32e32c64a603d8b
Author: Paul Thomas <pault@gcc.gnu.org>
Date:   Tue Apr 2 14:19:09 2024 +0100

    Fortran: Fix wrong recursive errors and class initialization [PR112407]

    2024-04-02  Paul Thomas  <pault@gcc.gnu.org>

    gcc/fortran
            PR fortran/112407
            * resolve.cc (resolve_procedure_expression): Change the test for
            for recursion in the case of hidden procedures from modules.
            (resolve_typebound_static): Add warning for possible recursive
            calls to typebound procedures.
            * trans-expr.cc (gfc_trans_class_init_assign): Do not apply
            default initializer to class dummy where component initializers
            are all null.

    gcc/testsuite/
            PR fortran/112407
            * gfortran.dg/pr112407a.f90: New test.
            * gfortran.dg/pr112407b.f90: New test.

^ permalink raw reply	[flat|nested] 13+ messages in thread

* [Bug fortran/112407] [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab
  2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
                   ` (10 preceding siblings ...)
  2024-04-02 13:19 ` cvs-commit at gcc dot gnu.org
@ 2024-04-23  9:45 ` pault at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: pault at gcc dot gnu.org @ 2024-04-23  9:45 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas <pault at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
            Summary|[13/14 Regression] Fix for  |[13 Regression] Fix for
                   |PR37336 triggers an ICE in  |PR37336 triggers an ICE in
                   |gfc_format_decoder while    |gfc_format_decoder while
                   |constructing a vtab         |constructing a vtab

--- Comment #11 from Paul Thomas <pault at gcc dot gnu.org> ---
Needs backporting. Summary changed.

^ permalink raw reply	[flat|nested] 13+ messages in thread

end of thread, other threads:[~2024-04-23  9:45 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2023-11-06 15:26 [Bug fortran/112407] New: [13 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab trnka at scm dot com
2023-11-06 15:27 ` [Bug fortran/112407] " trnka at scm dot com
2023-11-07  8:34 ` [Bug fortran/112407] [13/14 " rguenth at gcc dot gnu.org
2023-11-07 14:25 ` pault at gcc dot gnu.org
2023-11-07 16:04 ` trnka at scm dot com
2023-11-08 10:51 ` pault at gcc dot gnu.org
2023-11-08 15:32 ` trnka at scm dot com
2023-11-09 14:03 ` pault at gcc dot gnu.org
2024-03-29  7:57 ` pault at gcc dot gnu.org
2024-03-29 14:10 ` pault at gcc dot gnu.org
2024-03-30  7:27 ` pault at gcc dot gnu.org
2024-04-02 13:19 ` cvs-commit at gcc dot gnu.org
2024-04-23  9:45 ` [Bug fortran/112407] [13 " pault at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).