public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
@ 2022-11-22 17:41 gscfq@t-online.de
  2022-11-22 17:42 ` [Bug fortran/107819] " gscfq@t-online.de
                   ` (15 more replies)
  0 siblings, 16 replies; 17+ messages in thread
From: gscfq@t-online.de @ 2022-11-22 17:41 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 107819
           Summary: ICE in gfc_check_argument_var_dependency, at
                    fortran/dependency.cc:978
           Product: gcc
           Version: 13.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: gscfq@t-online.de
  Target Milestone: ---

Affects versions down to at least r5 :
(presumably processor dependent)


$ cat z1.f90
program p
   integer :: a(4) = [-1, -2, -3, -4]
   integer :: n(4) = [4, 2, 1, 3]
   call s (a(n), a)
   print *, a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ cat z2.f90
program p
   integer :: a(1) = [-1]
   integer :: n(1) = [1]
   call s (a(n), a)
   print *, a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ cat z6.f90
program p
   integer :: a(1) = [-1]
   integer :: n = 1
   call s (a(n:n), a)
   print *, a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ cat z7.f90
program p
   implicit none
   integer, parameter :: m = 99
   integer :: i
   integer :: a(m) = [(-i,i=1,m)]
   integer :: n(m) = [(i,i=m,1,-1)]
   call s (a(n), a)
   print *, a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ gfortran-13-20221120 -c z1.f90
z1.f90:4:19:

    4 |    call s (a(n), a)
      |                   1
internal compiler error: in gfc_check_argument_var_dependency, at
fortran/dependency.cc:978
0x8add39 gfc_check_argument_var_dependency
        ../../gcc/fortran/dependency.cc:978
0x8addcc gfc_check_argument_dependency
        ../../gcc/fortran/dependency.cc:1075
0x8addcc gfc_check_fncall_dependency(gfc_expr*, sym_intent, gfc_symbol*,
gfc_actual_arglist*, gfc_dep_check)
        ../../gcc/fortran/dependency.cc:1120
0x9640b0 gfc_conv_elemental_dependencies
        ../../gcc/fortran/trans-stmt.cc:267
0x9640b0 gfc_trans_call(gfc_code*, bool, tree_node*, tree_node*, bool)
        ../../gcc/fortran/trans-stmt.cc:491
0x8be656 trans_code
        ../../gcc/fortran/trans.cc:2018
0x8f5379 gfc_generate_function_code(gfc_namespace*)
        ../../gcc/fortran/trans-decl.cc:7674
0x86775e translate_all_program_units
        ../../gcc/fortran/parse.cc:6696
0x86775e gfc_parse_file()
        ../../gcc/fortran/parse.cc:7002
0x8b5a9f gfc_be_parse_file
        ../../gcc/fortran/f95-lang.cc:229

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
@ 2022-11-22 17:42 ` gscfq@t-online.de
  2022-11-22 19:41 ` anlauf at gcc dot gnu.org
                   ` (14 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: gscfq@t-online.de @ 2022-11-22 17:42 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #1 from G. Steinmetz <gscfq@t-online.de> ---

Works here with explicitly enforced evaluation (a(n)) :


$ cat z3.f90
program p
   integer :: a(4) = [-1, -2, -3, -4]
   integer :: n(4) = [4, 2, 1, 3]
   call s ((a(n)), a)
   print *, a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ cat z8.f90
program p
   implicit none
   integer, parameter :: m = 99
   integer :: i
   integer :: a(m) = [(-i,i=1,m)]
   call s ((a(m:1:-1)), a)
   print '(10i6)', a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ cat z9.f90
program p
   implicit none
   integer, parameter :: m = 99
   integer :: i
   integer :: a(m) = [(-i,i=1,m)]
   integer :: n(m) = [(i,i=m,1,-1)]
   call s ([a(n)], a)
   print '(10i6)', a
contains
   elemental subroutine s (x, y)
      integer, value :: x
      integer, intent(out) :: y
      y = x
   end
end


$ gfortran-13-20221120 z3.f90 && ./a.out
          -4          -2          -1          -3
$

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
  2022-11-22 17:42 ` [Bug fortran/107819] " gscfq@t-online.de
@ 2022-11-22 19:41 ` anlauf at gcc dot gnu.org
  2022-11-22 21:01 ` anlauf at gcc dot gnu.org
                   ` (13 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-22 19:41 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2022-11-22
           Keywords|                            |ice-on-invalid-code,
                   |                            |ice-on-valid-code
     Ever confirmed|0                           |1
                 CC|                            |anlauf at gcc dot gnu.org

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

Potential patch:

diff --git a/gcc/fortran/trans-stmt.cc b/gcc/fortran/trans-stmt.cc
index fd6d294147e..b288f1f9050 100644
--- a/gcc/fortran/trans-stmt.cc
+++ b/gcc/fortran/trans-stmt.cc
@@ -264,6 +264,7 @@ gfc_conv_elemental_dependencies (gfc_se * se, gfc_se *
loopse,
       if (e->expr_type == EXPR_VARIABLE
            && e->rank && fsym
            && fsym->attr.intent != INTENT_IN
+           && !fsym->attr.value
            && gfc_check_fncall_dependency (e, fsym->attr.intent,
                                            sym, arg0, check_variable))
        {

Note that we get a (correct) warning for z1 after this fix:

pr107819-z1.f90:4:10-16:

    4 |   call s (a(n), a)
      |          2     1
Warning: INTENT(OUT) actual argument at (1) might interfere with actual
argument at (2).

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
  2022-11-22 17:42 ` [Bug fortran/107819] " gscfq@t-online.de
  2022-11-22 19:41 ` anlauf at gcc dot gnu.org
@ 2022-11-22 21:01 ` anlauf at gcc dot gnu.org
  2022-11-24 13:12 ` mikael at gcc dot gnu.org
                   ` (12 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-22 21:01 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from anlauf at gcc dot gnu.org ---
(In reply to anlauf from comment #2)
> Potential patch:

This regtests ok.

However,

> Note that we get a (correct) warning for z1 after this fix:
> 
> pr107819-z1.f90:4:10-16:
> 
>     4 |   call s (a(n), a)
>       |          2     1
> Warning: INTENT(OUT) actual argument at (1) might interfere with actual
> argument at (2).

this comes from gfc_check_argument_var_dependency, where we see the INTENT(OUT)
argument a, we see a(n), and here

966           /* In case of elemental subroutines, there is no dependency
967              between two same-range array references.  */
968           if (gfc_ref_needs_temporary_p (expr->ref)
969               || gfc_check_dependency (var, expr, elemental ==
NOT_ELEMENTAL))

gfc_ref_needs_temporary_p (expr->ref) correctly returns true.
The comment sort of does not fit to what happens: the "range" is the same,
but n generates a permutation which is detected by gfc_ref_needs_temporary_p.
But then no temporary is generated for a(n), which means we miss a
corresponding check elsewhere.

Could need help by some expert on this...

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (2 preceding siblings ...)
  2022-11-22 21:01 ` anlauf at gcc dot gnu.org
@ 2022-11-24 13:12 ` mikael at gcc dot gnu.org
  2022-11-24 17:07 ` anlauf at gcc dot gnu.org
                   ` (11 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-11-24 13:12 UTC (permalink / raw)
  To: gcc-bugs

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

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |mikael at gcc dot gnu.org

--- Comment #4 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #3)
> But then no temporary is generated for a(n), which means we miss a
> corresponding check elsewhere.
> 
But is it required to generate a temporary?
As I understand it, the code is invalid, and (correctly) diagnosed, so there is
nothing else to do.
It's invalid because of 15.5.2.13 Restrictions on entities associated with
dummy arguments:
(4) If the value of the entity or any subobject of it is affected through the
dummy argument, then at any time during the invocation and execution of the
procedure, either before or after the definition, it shall be referenced only
through that dummy argument unless (...)

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (3 preceding siblings ...)
  2022-11-24 13:12 ` mikael at gcc dot gnu.org
@ 2022-11-24 17:07 ` anlauf at gcc dot gnu.org
  2022-11-24 19:07 ` mikael at gcc dot gnu.org
                   ` (10 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-24 17:07 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from anlauf at gcc dot gnu.org ---
(In reply to Mikael Morin from comment #4)
> But is it required to generate a temporary?
> As I understand it, the code is invalid, and (correctly) diagnosed, so there
> is nothing else to do.
> It's invalid because of 15.5.2.13 Restrictions on entities associated with
> dummy arguments:
> (4) If the value of the entity or any subobject of it is affected through
> the dummy argument, then at any time during the invocation and execution of
> the procedure, either before or after the definition, it shall be referenced
> only through that dummy argument unless (...)

Right.

I was confused by two observations.  First, NAG & Cray seem to generate
temporaries, while Intel and NVidia don't and would agree with gfortran
after the patch.

Second, I stumbled over:

! 15.5.2.3 Argument association
! (4) A present dummy argument with the VALUE attribute becomes argument
! associated with a definable anonymous data object whose initial value is
! the value of the actual argument.

So it boils down to what ELEMENTAL actually means in that context.  F2018:

15.8.3 Elemental subroutine actual arguments

! In a reference to an elemental subroutine, if the actual arguments
! corresponding to INTENT(OUT) and INTENT(INOUT) dummy arguments are
! arrays, the values of the elements, if any, of the results are the same
! as would be obtained if the subroutine had been applied separately, in
! array element order, to corresponding elements of each array actual
! argument.

So I read this that

   call s (a(n), a)

is to be interpreted as

  do i = 1, size (a)
     call s (a(n(i)), a(i))
  end do

and this would actually be well-defined behavior... ;-)

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (4 preceding siblings ...)
  2022-11-24 17:07 ` anlauf at gcc dot gnu.org
@ 2022-11-24 19:07 ` mikael at gcc dot gnu.org
  2022-11-24 21:24 ` anlauf at gcc dot gnu.org
                   ` (9 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-11-24 19:07 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #5)
> (In reply to Mikael Morin from comment #4)
> > But is it required to generate a temporary?
> > As I understand it, the code is invalid, and (correctly) diagnosed, so there
> > is nothing else to do.
> > It's invalid because of 15.5.2.13 Restrictions on entities associated with
> > dummy arguments:
> > (4) If the value of the entity or any subobject of it is affected through
> > the dummy argument, then at any time during the invocation and execution of
> > the procedure, either before or after the definition, it shall be referenced
> > only through that dummy argument unless (...)
> 
> Right.
> 
> I was confused by two observations.  First, NAG & Cray seem to generate
> temporaries, while Intel and NVidia don't and would agree with gfortran
> after the patch.
> 
> Second, I stumbled over:
> 
> ! 15.5.2.3 Argument association
> ! (4) A present dummy argument with the VALUE attribute becomes argument
> ! associated with a definable anonymous data object whose initial value is
> ! the value of the actual argument.
> 
Ouch! You're right, this makes the part I quoted above irrelevant.
And it explicitly asks for a temporary.

> So it boils down to what ELEMENTAL actually means in that context.  F2018:
> 
> 15.8.3 Elemental subroutine actual arguments
> 
> ! In a reference to an elemental subroutine, if the actual arguments
> ! corresponding to INTENT(OUT) and INTENT(INOUT) dummy arguments are
> ! arrays, the values of the elements, if any, of the results are the same
> ! as would be obtained if the subroutine had been applied separately, in
> ! array element order, to corresponding elements of each array actual
> ! argument.
> 
> So I read this that
> 
>    call s (a(n), a)
> 
> is to be interpreted as
> 
>   do i = 1, size (a)
>      call s (a(n(i)), a(i))
>   end do
> 
> and this would actually be well-defined behavior... ;-)

With your quote from 15.5.2.3 above, it would be more like:
do i = 1, size(a)
  tmp(i) = a(n(i))
end do
do i = 1, size(a)
  call s(tmp(i), a(i))
end do

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (5 preceding siblings ...)
  2022-11-24 19:07 ` mikael at gcc dot gnu.org
@ 2022-11-24 21:24 ` anlauf at gcc dot gnu.org
  2022-11-24 21:40 ` mikael at gcc dot gnu.org
                   ` (8 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-24 21:24 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from anlauf at gcc dot gnu.org ---
(In reply to Mikael Morin from comment #6)
> (In reply to anlauf from comment #5)
> > Second, I stumbled over:
> > 
> > ! 15.5.2.3 Argument association
> > ! (4) A present dummy argument with the VALUE attribute becomes argument
> > ! associated with a definable anonymous data object whose initial value is
> > ! the value of the actual argument.
> > 
> Ouch! You're right, this makes the part I quoted above irrelevant.
> And it explicitly asks for a temporary.

I've asked Intel if they agree with this interpretation.

In the meantime, do you have an idea where to force the generation of a
temporary?  I've been scrolling through gfc_conv_procedure_call to see
if that might be the right place, but that's not a small function...

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (6 preceding siblings ...)
  2022-11-24 21:24 ` anlauf at gcc dot gnu.org
@ 2022-11-24 21:40 ` mikael at gcc dot gnu.org
  2022-11-24 22:02 ` mikael at gcc dot gnu.org
                   ` (7 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-11-24 21:40 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #3)
> Could need help by some expert on this...

I guess I qualify as expert.
Reading the code again after years, it is not exactly crystal clear...

Here is a dump of what I could gather about the gfc_check_fncall_dependency and
friends functions.


The different gfc_dep_check cases are the following:


ELEM_DONT_CHECK_VARIABLE:
This is the simple case of direct subroutine call.
As per the 15.5.2.13 I quoted above, this is invalid:
  call elem_sub(a(2:n), a(1:n-1))
while this isn't
  call elem_sub(a, a)

so we can always generate:
  do i = ...
    call elem_sub(a(...), a(...))
  end do

without caring for temporaries


ELEM_CHECK_VARIABLE:
This is the case of multiple elemental procedures.
For example:
  call elem_sub(a, elem_func(a))

The semantics is like:
  tmp = elem_func(a)
  call elem_sub(a, tmp)

Here, elem_sub can write to a without modifying tmp, and we have to
preserve that.
We generate code like this:
  do i = ...
    call elem_sub(tmp(i), elem_func(a(i)))
  end do
  a = tmp
and try to avoid the temporary tmp if possible.
we explore the second argument to elem_sub and look for the same variable
as the expression from the first one, and we generate a temporary
if we find it.  But there is no need if they are strictly the same
variable reference.


NOT_ELEMENTAL:
This is the case of the presence of transpose in the expression
For example, for elem_sub(var, elem_func(transpose(var))), the semantics is:
  tmp1 = transpose(var)
  tmp2 = elem_func(tmp1)
  call elem_sub(var, tmp2)

which we try to preserve, but with less temporaries.
We try to generate
  do i = ..., j = ...
    call elem_sub(tmp(i,j), elem_func(var(j,i)))
  end do
  var = tmp

and try to avoid the temporary tmp if possible (it's not with this example).
We have to make sure that if the same variable appears in a subexpression
of the argument, a temporary is generated.
Contrary to the previous case, we have to generate the temporary
even if the variable references are strictly the same.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (7 preceding siblings ...)
  2022-11-24 21:40 ` mikael at gcc dot gnu.org
@ 2022-11-24 22:02 ` mikael at gcc dot gnu.org
  2022-11-25 22:06 ` anlauf at gcc dot gnu.org
                   ` (6 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-11-24 22:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #7)
> 
> In the meantime, do you have an idea where to force the generation of a
> temporary?  I've been scrolling through gfc_conv_procedure_call to see
> if that might be the right place, but that's not a small function...

It seems the semantics when an argument has the value attribute is the same as
the case ELEM_CHECK_VARIABLE in my previous comment.
So forcing the value of the elemental argument to ELEM_CHECK_VARIABLE at some
appropriate place could possibly work.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (8 preceding siblings ...)
  2022-11-24 22:02 ` mikael at gcc dot gnu.org
@ 2022-11-25 22:06 ` anlauf at gcc dot gnu.org
  2022-11-26 20:56 ` anlauf at gcc dot gnu.org
                   ` (5 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-25 22:06 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from anlauf at gcc dot gnu.org ---
Created attachment 53968
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=53968&action=edit
Revised patch

(In reply to Mikael Morin from comment #9)
> It seems the semantics when an argument has the value attribute is the same
> as the case ELEM_CHECK_VARIABLE in my previous comment.
> So forcing the value of the elemental argument to ELEM_CHECK_VARIABLE at
> some appropriate place could possibly work.

Many thanks for the explanations!

Looking at the involved code, the most simple solution I came up with is
attached.  It scans over the actual arguments associated with the dummies,
and when we find one with the VALUE attribute, we enforce the dependency
check.  It fixes the testcase and regtests fine.

I was struggling with the actual generated code, which is rather a temporary
for the arguments with INTENT(INOUT/OUT), but that should be functionally
equivalent.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (9 preceding siblings ...)
  2022-11-25 22:06 ` anlauf at gcc dot gnu.org
@ 2022-11-26 20:56 ` anlauf at gcc dot gnu.org
  2022-11-26 21:05 ` mikael at gcc dot gnu.org
                   ` (4 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-26 20:56 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from anlauf at gcc dot gnu.org ---
Update: Steve Lionel thinks that no temporary is necessary, and testcase z1.f90
is non-conforming:

https://community.intel.com/t5/Intel-Fortran-Compiler/ELEMENTAL-subroutine-and-dummy-with-VALUE-attribute/m-p/1432932

In this case the patch of comment#2 would be sufficient.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (10 preceding siblings ...)
  2022-11-26 20:56 ` anlauf at gcc dot gnu.org
@ 2022-11-26 21:05 ` mikael at gcc dot gnu.org
  2022-11-27 20:33 ` anlauf at gcc dot gnu.org
                   ` (3 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-11-26 21:05 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #11)
> Update: Steve Lionel thinks that no temporary is necessary, and testcase
> z1.f90
> is non-conforming:
> 
> https://community.intel.com/t5/Intel-Fortran-Compiler/ELEMENTAL-subroutine-
> and-dummy-with-VALUE-attribute/m-p/1432932
> 
> In this case the patch of comment#2 would be sufficient.

I was about to suggest to push the check_variable value change down into
gfc_check_fncall_dependency, to be more aggressive wrt temporary elimination.
But if the test is not conforming, let's throw all that away.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (11 preceding siblings ...)
  2022-11-26 21:05 ` mikael at gcc dot gnu.org
@ 2022-11-27 20:33 ` anlauf at gcc dot gnu.org
  2022-11-28 18:54 ` cvs-commit at gcc dot gnu.org
                   ` (2 subsequent siblings)
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-27 20:33 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED
           Assignee|unassigned at gcc dot gnu.org      |anlauf at gcc dot gnu.org

--- Comment #13 from anlauf at gcc dot gnu.org ---
Submitted: https://gcc.gnu.org/pipermail/fortran/2022-November/058556.html

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (12 preceding siblings ...)
  2022-11-27 20:33 ` anlauf at gcc dot gnu.org
@ 2022-11-28 18:54 ` cvs-commit at gcc dot gnu.org
  2022-11-28 21:27 ` anlauf at gcc dot gnu.org
  2022-11-28 21:57 ` pinskia at gcc dot gnu.org
  15 siblings, 0 replies; 17+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2022-11-28 18:54 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #14 from CVS Commits <cvs-commit at gcc dot gnu.org> ---
The master branch has been updated by Harald Anlauf <anlauf@gcc.gnu.org>:

https://gcc.gnu.org/g:07b9bcc1d1484f8f1c850ff14db678fb6b1e4d36

commit r13-4375-g07b9bcc1d1484f8f1c850ff14db678fb6b1e4d36
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Sun Nov 27 21:10:18 2022 +0100

    Fortran: ICE with elemental and dummy argument with VALUE attribute
[PR107819]

    gcc/fortran/ChangeLog:

            PR fortran/107819
            * trans-stmt.cc (gfc_conv_elemental_dependencies): In checking for
            elemental dependencies, treat dummy argument with VALUE attribute
            as implicitly having intent(in).

    gcc/testsuite/ChangeLog:

            PR fortran/107819
            * gfortran.dg/elemental_dependency_7.f90: New test.

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (13 preceding siblings ...)
  2022-11-28 18:54 ` cvs-commit at gcc dot gnu.org
@ 2022-11-28 21:27 ` anlauf at gcc dot gnu.org
  2022-11-28 21:57 ` pinskia at gcc dot gnu.org
  15 siblings, 0 replies; 17+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-11-28 21:27 UTC (permalink / raw)
  To: gcc-bugs

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

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         Resolution|---                         |FIXED
             Status|ASSIGNED                    |RESOLVED

--- Comment #15 from anlauf at gcc dot gnu.org ---
Fixed on mainline for gcc-13.  Closing.

Thanks for the report!

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

* [Bug fortran/107819] ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978
  2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
                   ` (14 preceding siblings ...)
  2022-11-28 21:27 ` anlauf at gcc dot gnu.org
@ 2022-11-28 21:57 ` pinskia at gcc dot gnu.org
  15 siblings, 0 replies; 17+ messages in thread
From: pinskia at gcc dot gnu.org @ 2022-11-28 21:57 UTC (permalink / raw)
  To: gcc-bugs

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

Andrew Pinski <pinskia at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|---                         |13.0

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

end of thread, other threads:[~2022-11-28 21:57 UTC | newest]

Thread overview: 17+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2022-11-22 17:41 [Bug fortran/107819] New: ICE in gfc_check_argument_var_dependency, at fortran/dependency.cc:978 gscfq@t-online.de
2022-11-22 17:42 ` [Bug fortran/107819] " gscfq@t-online.de
2022-11-22 19:41 ` anlauf at gcc dot gnu.org
2022-11-22 21:01 ` anlauf at gcc dot gnu.org
2022-11-24 13:12 ` mikael at gcc dot gnu.org
2022-11-24 17:07 ` anlauf at gcc dot gnu.org
2022-11-24 19:07 ` mikael at gcc dot gnu.org
2022-11-24 21:24 ` anlauf at gcc dot gnu.org
2022-11-24 21:40 ` mikael at gcc dot gnu.org
2022-11-24 22:02 ` mikael at gcc dot gnu.org
2022-11-25 22:06 ` anlauf at gcc dot gnu.org
2022-11-26 20:56 ` anlauf at gcc dot gnu.org
2022-11-26 21:05 ` mikael at gcc dot gnu.org
2022-11-27 20:33 ` anlauf at gcc dot gnu.org
2022-11-28 18:54 ` cvs-commit at gcc dot gnu.org
2022-11-28 21:27 ` anlauf at gcc dot gnu.org
2022-11-28 21:57 ` pinskia 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).