[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-09-28 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

anlauf at gcc dot gnu.org changed:

   What|Removed |Added

 CC||antoine.lemoine@bordeaux-in
   ||p.fr

--- Comment #24 from anlauf at gcc dot gnu.org ---
*** Bug 111618 has been marked as a duplicate of this bug. ***

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-09-07 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

anlauf at gcc dot gnu.org changed:

   What|Removed |Added

   Target Milestone|13.2|13.3

--- Comment #23 from anlauf at gcc dot gnu.org ---
The fix was applied to 13-branch after the 13.2 release.
Updating target milestone appropriately.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-09-07 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

anlauf at gcc dot gnu.org changed:

   What|Removed |Added

 CC||alexandre.poux at coria dot fr

--- Comment #22 from anlauf at gcc dot gnu.org ---
*** Bug 111321 has been marked as a duplicate of this bug. ***

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-08-27 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #21 from CVS Commits  ---
The releases/gcc-13 branch has been updated by Paul Thomas :

https://gcc.gnu.org/g:d6997a5aab7aaa325946a6283bfee8ac2bd9f540

commit r13-7761-gd6997a5aab7aaa325946a6283bfee8ac2bd9f540
Author: Paul Thomas 
Date:   Sun Aug 27 09:51:32 2023 +0100

Fortran: Fix some problems blocking associate meta-bug [PR87477]

2023-08-27  Paul Thomas  

gcc/fortran
PR fortran/87477
* parse.cc (parse_associate): Replace the existing evaluation
of the target rank with calls to gfc_resolve_ref and
gfc_expression_rank. Identify untyped target function results
with structure constructors by finding the appropriate derived
type.
* resolve.cc (resolve_symbol): Allow associate variables to be
assumed shape.

gcc/testsuite/
PR fortran/87477
* gfortran.dg/associate_54.f90 : Cope with extra error.

PR fortran/102109
* gfortran.dg/pr102109.f90 : New test.

PR fortran/102112
* gfortran.dg/pr102112.f90 : New test.

PR fortran/102190
* gfortran.dg/pr102190.f90 : New test.

PR fortran/102532
* gfortran.dg/pr102532.f90 : New test.

PR fortran/109948
* gfortran.dg/pr109948.f90 : New test.

PR fortran/99326
* gfortran.dg/pr99326.f90 : New test.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-06-02 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

Paul Thomas  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #20 from Paul Thomas  ---
Fixed on trunk. I am closing the PR for housekeeping purposes but will include
the patch in future backports.

Thanks for the report.

Paul

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-06-02 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #19 from Paul Thomas  ---
(In reply to anlauf from comment #16)
> (In reply to Paul Thomas from comment #15)
> > Created attachment 55225 [details]
> > Fix for this PR
> > 
> > The attached patch substantially tidies up parse_associate and fixes:
> 
> LGTM!
> 
> I was close to proposing a hack for gfc_expression_rank that checks
> whether the variable's select_type_temporary, select_rank_temporary and
> associate_var attributes to decide which ref to evaluate.  But your
> patch seems to be a much better approach.
> 
> BTW: after your patch, the attribute assoc->rankguessed is no longer set.
> It is tested in two locations in resolve_assoc_var(resolve.cc), where
> it might be removed after your fix.

On the latter => yes indeed!

I see that I had a fix for pr109451, which was never submitted. I am going to
shake the dust off the patch and will set about removing rankguessed.

Thanks

Paul

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-06-02 Thread cvs-commit at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #18 from CVS Commits  ---
The master branch has been updated by Paul Thomas :

https://gcc.gnu.org/g:3c2eba4b7a2355ed5099e35332388206c484744d

commit r14-1487-g3c2eba4b7a2355ed5099e35332388206c484744d
Author: Paul Thomas 
Date:   Fri Jun 2 08:41:45 2023 +0100

Fortran: Fix some problems blocking associate meta-bug [PR87477]

2023-06-02  Paul Thomas  

gcc/fortran
PR fortran/87477
* parse.cc (parse_associate): Replace the existing evaluation
of the target rank with calls to gfc_resolve_ref and
gfc_expression_rank. Identify untyped target function results
with structure constructors by finding the appropriate derived
type.
* resolve.cc (resolve_symbol): Allow associate variables to be
assumed shape.

gcc/testsuite/
PR fortran/87477
* gfortran.dg/associate_54.f90 : Cope with extra error.

PR fortran/102109
* gfortran.dg/pr102109.f90 : New test.

PR fortran/102112
* gfortran.dg/pr102112.f90 : New test.

PR fortran/102190
* gfortran.dg/pr102190.f90 : New test.

PR fortran/102532
* gfortran.dg/pr102532.f90 : New test.

PR fortran/109948
* gfortran.dg/pr109948.f90 : New test.

PR fortran/99326
* gfortran.dg/pr99326.f90 : New test.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-31 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #17 from Mikael Morin  ---
(In reply to anlauf from comment #16)
> (In reply to Paul Thomas from comment #15)
> > Created attachment 55225 [details]
> > Fix for this PR
> > 
> > The attached patch substantially tidies up parse_associate and fixes:
> 
> LGTM!
> 
Yes, nice work.  I didn't expect such a simple fix.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-31 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #16 from anlauf at gcc dot gnu.org ---
(In reply to Paul Thomas from comment #15)
> Created attachment 55225 [details]
> Fix for this PR
> 
> The attached patch substantially tidies up parse_associate and fixes:

LGTM!

I was close to proposing a hack for gfc_expression_rank that checks
whether the variable's select_type_temporary, select_rank_temporary and
associate_var attributes to decide which ref to evaluate.  But your
patch seems to be a much better approach.

BTW: after your patch, the attribute assoc->rankguessed is no longer set.
It is tested in two locations in resolve_assoc_var(resolve.cc), where
it might be removed after your fix.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-31 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

Paul Thomas  changed:

   What|Removed |Added

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

--- Comment #15 from Paul Thomas  ---
Created attachment 55225
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=55225=edit
Fix for this PR

The attached patch substantially tidies up parse_associate and fixes:

! { dg-do run }
!
! Tests the fix for PR109948
!
module mm
  implicit none
  interface operator(==)
module procedure eq_1_2
  end interface operator(==)
  private :: eq_1_2
contains
  logical function eq_1_2 (x, y)
integer, intent(in) :: x(:)
real,intent(in) :: y(:,:)
eq_1_2 = .true.
  end function eq_1_2
end module mm

program pr109948
  use mm
  implicit none
  type tlap
integer,allocatable :: z(:)
  end type tlap
  type ulap
type(tlap) :: u(2)
  end type ulap
  integer :: pid = 1
  call comment0 ! Original problem
  call comment1
  call comment3 ([5,4,3,2,1])
  call comment10
  call comment11 ([5,4,3,2,1])
contains
  subroutine comment0
type(tlap) :: y_in
integer :: x_out(3) =[0.0,0.0,0.0]
y_in%z = [1,-2,3]
call foo(y_in, x_out)
if (any (x_out .ne. [0, -2, 0])) stop 1
call foo(y_in, x_out)
if (any (x_out .ne. [1, -2, 3])) stop 2
  end subroutine comment0

  subroutine foo(y, x)
type(tlap) :: y
integer :: x(:)
associate(z=>y%z)
  if (pid == 1) then
where ( z < 0 ) x(:) = z(:)
  else
where ( z > 0 ) x(:) = z(:)
endif
pid = pid + 1
end associate
  end subroutine foo

  subroutine comment1
type(tlap) :: grib
integer :: i
grib%z = [3,2,1]
associate(k=>grib%z)
  i = k(1)
  if (any(k==1)) i = 1
end associate
if (i .eq. 3) stop 3
  end subroutine comment1

  subroutine comment3(k_2d)
implicit none
integer :: k_2d(:)
integer :: i
associate(k=>k_2d)
  i = k(1)
  if (any(k==1)) i = 1
end associate
if (i .eq. 3) stop 4
  end subroutine comment3

  subroutine comment11(k_2d)
implicit none
integer :: k_2d(:)
integer :: m(1) = 42
real:: r(1,1) = 3.0
if ((m == r) .neqv. .true.) stop 5
associate (k=>k_2d)
  if ((k == r) .neqv. .true.) stop 6  ! failed to find user defined
operator
end associate
associate (k=>k_2d(:))
  if ((k == r) .neqv. .true.) stop 7
end associate
  end subroutine comment11

  subroutine comment10
implicit none
type(ulap) :: z(2)
integer :: i
real:: r(1,1) = 3.0
z(1)%u = [tlap([1,2,3]),tlap([4,5,6])]
z(2)%u = [tlap([7,8,9]),tlap([10,11,12])]
associate (k=>z(2)%u(1)%z)
  i = k(1)
  if (any(k==8)) i = 1
end associate
if (i .ne. 1) stop 8
associate (k=>z(1)%u(2)%z)
  if ((k == r) .neqv. .true.) stop 9
  if (any (k .ne. [4,5,6])) stop 10
end associate
  end subroutine comment10
end program pr109948

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-30 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #14 from Paul Thomas  ---
Hi Mikael,


> Mmh, in a sense it also "double breaks" it. For example, with
> associate(z=>array(1)%ar(2,3)%array(:,:,:)), I expect to get the wrong as in
> ref->u.ar.as for the last two array references.
> You probably want to copy what's done in find_array_spec or directly call it?

Agreed - working both on parse_associate and gfc_expression_rank provides most
of the required repairs. However, the target expression is so incomplete during
parsing that this fails as before:

> 
> My opinion remains that calling eval_intrinsic at parsing time (as it
> appears we do from the stack trace) is fundamentally too early.  It doesn't
> make sure that everything is properly set up, and that all the rules of the
> standard are respected.  We wouldn't have this problem if the call to
> eval_intrinsic was deferred to the resolution time.


  subroutine comment10
implicit none
type(ulap) :: z(2)
integer :: i
real:: r(1,1) = 3.0
z(1)%u = [tlap([1,2,3]),tlap([4,5,6])]
z(2)%u = [tlap([7,8,9]),tlap([10,11,12])]
associate (k=>z(2)%u(1)%z)
  i = k(1)
  if (any(k==8)) i = 1 ! This is OK
end associate
if (i .ne. 1) stop 8
associate (k=>z(1)%u(2)%z)
  print *, k
  if ((k == r) .neqv. .true.) stop 9   ! Still broken
end associate
  end subroutine comment10

Unfortunately, resolving the target expression in parse_associate causes a
large number of regressions (I stopped the regression test after the 'a's). So,
yes, you are quite right about the timing, especially in regard of operator
interfaces.

Andy Vaught's obsession with single pass parsing is biting us in the posterior.

I'll report back later on where I have got to with this PR.

Cheers

Paul

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #13 from anlauf at gcc dot gnu.org ---
(In reply to anlauf from comment #12)
> +   && e->symtree->n.sym->assoc->target->ref
> +   && e->symtree->n.sym->assoc->target->ref->u.ar.type == AR_FULL
> +   && e->symtree->n.sym->assoc->target->ref->u.ar.as)
> + {
> +   e->rank = e->symtree->n.sym->assoc->target->ref->u.ar.as->rank;
> +   goto done;
> + }
> +

Maybe be just need to follow the refs and join the code with the later part.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #12 from anlauf at gcc dot gnu.org ---
(In reply to anlauf from comment #11)
> I think it does not handle the following variation of the testcase from
> the blamed patch:

This one seems to be handled by the clumsy attempt:

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 75d61a18856..a5dcf07c1ee 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -5622,6 +5625,21 @@ gfc_expression_rank (gfc_expr *e)
 {
   if (e->expr_type == EXPR_ARRAY)
goto done;
+
+  /* Take rank from associate target.  */
+  if (e->symtree
+ && e->symtree->n.sym->as == NULL
+ && e->symtree->n.sym->assoc
+ && e->symtree->n.sym->assoc->target
+ && e->symtree->n.sym->assoc->rankguessed
+ && e->symtree->n.sym->assoc->target->ref
+ && e->symtree->n.sym->assoc->target->ref->u.ar.type == AR_FULL
+ && e->symtree->n.sym->assoc->target->ref->u.ar.as)
+   {
+ e->rank = e->symtree->n.sym->assoc->target->ref->u.ar.as->rank;
+ goto done;
+   }
+
   /* Constructors can have a rank different from one via RESHAPE().  */

   e->rank = ((e->symtree == NULL || e->symtree->n.sym->as == NULL)
@@ -5640,7 +5658,7 @@ gfc_expression_rank (gfc_expr *e)
   if (ref->type != REF_ARRAY)
continue;

-  if (ref->u.ar.type == AR_FULL)
+  if (ref->u.ar.type == AR_FULL && ref->u.ar.as)
{
  rank = ref->u.ar.as->rank;
  break;


Of course this does not address the point brought up by Mikael.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #11 from anlauf at gcc dot gnu.org ---
(In reply to Paul Thomas from comment #9)
> By the way, the patch regtests OK
> 
> Do you want to do the honours or shall I?
> 
> I think that this rates as an 'obvious' fix.

I think it does not handle the following variation of the testcase from
the blamed patch:


module mm
  implicit none
  interface operator(==)
 module procedure eq_1_2
  end interface operator(==)
  private :: eq_1_2
contains
  logical function eq_1_2 (x, y)
integer, intent(in) :: x(:)
real,intent(in) :: y(:,:)
eq_1_2 = .true.
  end function eq_1_2
end module mm

subroutine foo(k_2d)
  use mm
  implicit none
  integer :: k_2d(:)
  integer :: m(1) = 42
  real:: r(1,1) = 3.0
  print *, (m == r)
  associate (k=>k_2d)
print *, (k == r)   ! <-- fails
  end associate
  associate (k=>k_2d(:))
print *, (k == r)
  end associate
end subroutine foo


For the marked line, I see in the debugger that e->ref == NULL.
I've played with some modification of the related code block, but that
regressed on two of the associate testcases.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread mikael at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

Mikael Morin  changed:

   What|Removed |Added

 CC||mikael at gcc dot gnu.org

--- Comment #10 from Mikael Morin  ---
(In reply to Paul Thomas from comment #8)
> I have flagged that this PR blocks PR87477.
> 
> Guarding ref->u.ar.as is good practice. However, it turns out that the
> associate name symbol has a perfectly good array_spec. This version "double
> fixes" the PR and is somewhat more satisfactory.
> 
> diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
> index 83e45f1b693..9863cdc1583 100644
> --- a/gcc/fortran/resolve.cc
> +++ b/gcc/fortran/resolve.cc
> @@ -5640,7 +5640,12 @@ gfc_expression_rank (gfc_expr *e)
>if (ref->type != REF_ARRAY)
> continue;
>  
> -  if (ref->u.ar.type == AR_FULL)
> +  if (ref->u.ar.as == NULL
> + && e->expr_type == EXPR_VARIABLE
> + && e->symtree->n.sym->as)
> +   ref->u.ar.as = e->symtree->n.sym->as;
> +
> +  if (ref->u.ar.type == AR_FULL && ref->u.ar.as)
> {
>   rank = ref->u.ar.as->rank;
>   break;
> 

Mmh, in a sense it also "double breaks" it. For example, with
associate(z=>array(1)%ar(2,3)%array(:,:,:)), I expect to get the wrong as in
ref->u.ar.as for the last two array references.
You probably want to copy what's done in find_array_spec or directly call it?

My opinion remains that calling eval_intrinsic at parsing time (as it appears
we do from the stack trace) is fundamentally too early.  It doesn't make sure
that everything is properly set up, and that all the rules of the standard are
respected.  We wouldn't have this problem if the call to eval_intrinsic was
deferred to the resolution time.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #9 from Paul Thomas  ---
By the way, the patch regtests OK

Do you want to do the honours or shall I?

I think that this rates as an 'obvious' fix.

Paul

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-26 Thread pault at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

Paul Thomas  changed:

   What|Removed |Added

 Blocks||87477

--- Comment #8 from Paul Thomas  ---
I have flagged that this PR blocks PR87477.

Guarding ref->u.ar.as is good practice. However, it turns out that the
associate name symbol has a perfectly good array_spec. This version "double
fixes" the PR and is somewhat more satisfactory.

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 83e45f1b693..9863cdc1583 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -5640,7 +5640,12 @@ gfc_expression_rank (gfc_expr *e)
   if (ref->type != REF_ARRAY)
continue;

-  if (ref->u.ar.type == AR_FULL)
+  if (ref->u.ar.as == NULL
+ && e->expr_type == EXPR_VARIABLE
+ && e->symtree->n.sym->as)
+   ref->u.ar.as = e->symtree->n.sym->as;
+
+  if (ref->u.ar.type == AR_FULL && ref->u.ar.as)
{
  rank = ref->u.ar.as->rank;
  break;

Gratifyingly, this does the right thing:

  implicit none
  type tlap
real,allocatable :: z(:)
  end type tlap
  type(tlap) :: y_in
  real :: x_out(3) =[0.0,0.0,0.0]
  integer :: pid = 1
  y_in%z = [1.0,-2.0,3.0]
  call foo(y_in, x_out)
  print *, x_out
  call foo(y_in, x_out)
  print *, x_out
contains
  subroutine foo(y, x)
type(tlap) :: y
real :: x(:)
associate(z=>y%z)

if (getpid() == 1) then
  where ( z < 0.0 ) x(:) = z(:)
else
  where ( z > 0.0 ) x(:) = z(:)
endif

end associate
  end subroutine foo
  integer function getpid()
getpid = pid
pid = pid + 1
  end function getpid
end

Cheers

Paul


Referenced Bugs:

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87477
[Bug 87477] [meta-bug] [F03] issues concerning the ASSOCIATE statement

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-25 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #7 from anlauf at gcc dot gnu.org ---
Some more digging: in the case when ref->u.ar.as is NULL, it appears that

e->symtree->n.sym->assoc->target->ref->u.ar.as

is properly set.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-25 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

anlauf at gcc dot gnu.org changed:

   What|Removed |Added

 CC||pault at gcc dot gnu.org

--- Comment #6 from anlauf at gcc dot gnu.org ---
(In reply to Rimvydas (RJ) from comment #5)
> (In reply to anlauf from comment #4)
> > Can you check if this works for you?
> 
> This patch allows to avoid issue on all other associate use cases (tried on
> gcc-13 branch).
> 
> However it is a bit suspicious that using variable name abbreviations (to
> dig out arrays from deeply nested types) is enough to change how the
> internal gfc_array_ref is populated.  ICE was triggered only on patterns
> involving first using abbreviated name indexed access (like k(1)) followed
> by any operation involving whole array.

I agree that this patch is a band-aid, possibly for some latent issue.
The suspect patch may have affected the order of resolution.

Note that replacing in the reduced testcase in comment#3:

  associate(k=>k_2d)

by

  associate(k=>k_2d(:))

avoids the ICE and gives identical code for gcc-12 .. gcc-14.  In fact,
the array-spec seems properly set.

I've added Paul in CC, who is more familiar with the associate construct.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-25 Thread rguenth at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

Richard Biener  changed:

   What|Removed |Added

   Priority|P3  |P4
   Target Milestone|--- |13.2

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-24 Thread rimvydas.jas at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #5 from Rimvydas (RJ)  ---
(In reply to anlauf from comment #4)
> Can you check if this works for you?

This patch allows to avoid issue on all other associate use cases (tried on
gcc-13 branch).

However it is a bit suspicious that using variable name abbreviations (to dig
out arrays from deeply nested types) is enough to change how the internal
gfc_array_ref is populated.  ICE was triggered only on patterns involving first
using abbreviated name indexed access (like k(1)) followed by any operation
involving whole array.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-24 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #4 from anlauf at gcc dot gnu.org ---
The following patch fixes NULL pointer dereference with the reduced
testcases:

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 83e45f1b693..89c62b3eb1e 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -5640,7 +5643,7 @@ gfc_expression_rank (gfc_expr *e)
   if (ref->type != REF_ARRAY)
continue;

-  if (ref->u.ar.type == AR_FULL)
+  if (ref->u.ar.type == AR_FULL && ref->u.ar.as)
{
  rank = ref->u.ar.as->rank;
  break;

Can you check if this works for you?

Still needs regtesting.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-24 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

--- Comment #3 from anlauf at gcc dot gnu.org ---
(In reply to Rimvydas (RJ) from comment #1)
> More trivial testcase resulting in similar ICE.

Yep, even smaller:

subroutine foo(k_2d)
  implicit none
  integer :: k_2d(:)
  integer :: i
  associate(k=>k_2d)
i = k(1)
if (any(k==1)) i = 1
  end associate
end subroutine foo

The associate is apparently one of the common components that is needed.

[Bug fortran/109948] [13/14 Regression] ICE(segfault) in gfc_expression_rank() from gfc_op_rank_conformable()

2023-05-24 Thread anlauf at gcc dot gnu.org via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109948

anlauf at gcc dot gnu.org changed:

   What|Removed |Added

   Keywords||ice-on-valid-code
 Ever confirmed|0   |1
 Status|UNCONFIRMED |NEW
 CC||anlauf at gcc dot gnu.org
Summary|ICE(segfault) in|[13/14 Regression]
   |gfc_expression_rank() from  |ICE(segfault) in
   |gfc_op_rank_conformable()   |gfc_expression_rank() from
   ||gfc_op_rank_conformable()
   Last reconfirmed||2023-05-24

--- Comment #2 from anlauf at gcc dot gnu.org ---
Confirmed.

Further reduced:

subroutine foo(y, x)
  implicit none
  real :: y(:)
  real :: x(:)

  associate(z=>y)
where ( z < 0.0 ) x(:) = z(:)
where ( z < 0.0 ) x(:) = z(:)
  end associate

end subroutine foo