[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-04-02 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #10 from GCC Commits  ---
The master branch has been updated by Paul Thomas :

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

commit r14-9752-g35408b3669fac104cd380582b32e32c64a603d8b
Author: Paul Thomas 
Date:   Tue Apr 2 14:19:09 2024 +0100

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

2024-04-02  Paul Thomas  

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.

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #9 from Paul Thomas  ---
(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

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #8 from Paul Thomas  ---
Created attachment 57835
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57835=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

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2024-03-29 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #7 from Paul Thomas  ---
Created attachment 57833
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57833=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

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-09 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #6 from Paul Thomas  ---
(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

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-08 Thread trnka at scm dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #5 from Tomáš Trnka  ---
(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.

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-08 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas  changed:

   What|Removed |Added

   Assignee|unassigned at gcc dot gnu.org  |pault at gcc dot gnu.org

--- Comment #4 from Paul Thomas  ---
Created attachment 56531
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=56531=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

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-07 Thread trnka at scm dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

--- Comment #3 from Tomáš Trnka  ---
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.

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-07 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Paul Thomas  changed:

   What|Removed |Added

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

--- Comment #2 from Paul Thomas  ---
(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))

[Bug fortran/112407] [13/14 Regression] Fix for PR37336 triggers an ICE in gfc_format_decoder while constructing a vtab

2023-11-07 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=112407

Richard Biener  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