public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy
@ 2024-01-13 14:21 anlauf at gcc dot gnu.org
  2024-01-14 10:51 ` [Bug fortran/113377] " mikael at gcc dot gnu.org
                   ` (11 more replies)
  0 siblings, 12 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-13 14:21 UTC (permalink / raw)
  To: gcc-bugs

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

            Bug ID: 113377
           Summary: Wrong code passing optional dummy argument to
                    elemental procedure with optional dummy
           Product: gcc
           Version: 14.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: anlauf at gcc dot gnu.org
  Target Milestone: ---

There are likely several related PRs, e.g. pr67277, but here is a smaller
reproducer:

program p
  implicit none
  integer :: k(4) = 1, m(4)
  m = one (k)
  print *, m
contains
  function one (i, j) result (r)
    integer, intent(in)           :: i(4)
    integer, intent(in), optional :: j
    integer                       :: r(size(i))
    r = two (i, j)  ! scalarizer dereferences loop invariant j ...
  end

  elemental function two (i, j) result (r)
    integer, intent(in)           :: i
    integer, value,      optional :: j
    integer                       :: r
    r = 42*i
  end
end

This crashes in function one.  A scalar invocation does not fail.
The dump-tree suggests that the scalarizer sees the loop invariant j,
unconditionally dereferences it outside the loop, generates code that
unconditionally dereferences j in the invocation of two, and uses a
wrong interface:

integer(kind=4) two (integer(kind=4) & restrict i, integer(kind=4) j,
logical(kind=1) .j)

but one has:

    D.4339 = (integer(kind=4) *) j;
    {
      integer(kind=8) S.3;
      integer(kind=8) D.4341;

      D.4341 = stride.0;
      S.3 = 1;
      while (1)
        {
          if (S.3 > 4) goto L.1;
          *((integer(kind=4) *) __result.0 + (sizetype) ((S.3 * D.4341 +
D.4338) * 4)) = two (&(*i)[S.3 + -1], *D.4339);
          S.3 = S.3 + 1;
        }
      L.1:;

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
@ 2024-01-14 10:51 ` mikael at gcc dot gnu.org
  2024-01-14 20:05 ` anlauf at gcc dot gnu.org
                   ` (10 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-01-14 10:51 UTC (permalink / raw)
  To: gcc-bugs

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

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

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

--- Comment #1 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #0)
> The dump-tree suggests that the scalarizer sees the loop invariant j,
> unconditionally dereferences it outside the loop,

Note that the copy to the variable before the loop does NOT dereference the
pointer.
This case is explicitly supported by the scalarizer, see
gfc_scalar_elemental_arg_saved_as_reference (and
gfc_walk_elemental_function_args for the initialization of the can_be_null_ref
field).

Normally this is sufficient to support optional dummies (there is also
additional support for class wrappers in gfc_conv_procedure_call), except if
value comes into play.

> generates code that
> unconditionally dereferences j in the invocation of two, and uses a
> wrong interface:
These are the topics to investigate.
I suppose we need to duplicate (or factor) the code for optional, value dummies
that was added for non-elemental procedures in gfc_conv_procedure_call.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
  2024-01-14 10:51 ` [Bug fortran/113377] " mikael at gcc dot gnu.org
@ 2024-01-14 20:05 ` anlauf at gcc dot gnu.org
  2024-01-16 21:05 ` anlauf at gcc dot gnu.org
                   ` (9 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-14 20:05 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from anlauf at gcc dot gnu.org ---
(In reply to Mikael Morin from comment #1)
> (In reply to anlauf from comment #0)
> > The dump-tree suggests that the scalarizer sees the loop invariant j,
> > unconditionally dereferences it outside the loop,
> 
> Note that the copy to the variable before the loop does NOT dereference the
> pointer.

You are right: I was mistaken as I was looking at the code generated for
PR67277, especially at testcase gfortran.dg/ishftc_optional_size_1.f90,
function ishftc4_ref_4, where the scalarization deferences the optional
argument size_,

    D.4389 = *size_;

outside of the loop.

> This case is explicitly supported by the scalarizer, see
> gfc_scalar_elemental_arg_saved_as_reference (and
> gfc_walk_elemental_function_args for the initialization of the
> can_be_null_ref field).

I'll need to have a closer look here.

Note that adding a scalar call in function one:

    r(1) = two (i(1), j)

generates sane code:

  *((integer(kind=4) *) __result.0 + (sizetype) ((offset.1 + NON_LVALUE_EXPR
<stride.0>) * 4)) = two (&(*i)[0], j != 0B ? *j : 0, j != 0B);

> Normally this is sufficient to support optional dummies (there is also
> additional support for class wrappers in gfc_conv_procedure_call), except if
> value comes into play.
> 
> > generates code that
> > unconditionally dereferences j in the invocation of two, and uses a
> > wrong interface:
> These are the topics to investigate.
> I suppose we need to duplicate (or factor) the code for optional, value
> dummies that was added for non-elemental procedures in
> gfc_conv_procedure_call.

Probably yes.

There is another observation: using the value attribute for j also in one,
the scalar call from above becomes a straight

  *((integer(kind=4) *) __result.0 + (sizetype) ((offset.1 + NON_LVALUE_EXPR
<stride.0>) * 4)) = two (&(*i)[0], j, .j);

while the scalarizer produces:

    integer(kind=4) * D.4340;
...
    D.4340 = &j;
...
          *((integer(kind=4) *) __result.0 + (sizetype) ((S.3 * D.4342 +
D.4339) * 4)) = two (&(*i)[S.3 + -1], *D.4340);

which looks more complicated (besides being wrong...)

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
  2024-01-14 10:51 ` [Bug fortran/113377] " mikael at gcc dot gnu.org
  2024-01-14 20:05 ` anlauf at gcc dot gnu.org
@ 2024-01-16 21:05 ` anlauf at gcc dot gnu.org
  2024-01-16 22:02 ` anlauf at gcc dot gnu.org
                   ` (8 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-16 21:05 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from anlauf at gcc dot gnu.org ---
Created attachment 57108
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57108&action=edit
Patch to play with

This is a first attempt to outline code for handling scalar dummies with the
VALUE attribute.

This fixes the following variants of the declaration of dummy argument j
in function one:

    integer, value,      optional :: j
    integer, intent(in), optional :: j
    integer, intent(in), optional :: j(4)
    integer, intent(in), optional :: j(:)

However,

    integer, allocatable,optional :: j

still does not work: the code *in* the generated loop looks fine to me, but
the scalarizer dereferences j before the loop.

I think that this is correct F2018+, as ifx handles it fine.
Not sure how to proceed here.


Furthermore, the patch tries to cope (= prevent an ICE) with

    integer, allocatable,optional :: j(:)

which I think might be invalid.  At least it also crashed with ifx...

Otherwise, the patch so far regtests ok.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2024-01-16 21:05 ` anlauf at gcc dot gnu.org
@ 2024-01-16 22:02 ` anlauf at gcc dot gnu.org
  2024-01-19 18:46 ` mikael at gcc dot gnu.org
                   ` (7 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-16 22:02 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from anlauf at gcc dot gnu.org ---
(In reply to anlauf from comment #3)
> However,
> 
>     integer, allocatable,optional :: j
> 
> still does not work: the code *in* the generated loop looks fine to me, but
> the scalarizer dereferences j before the loop.

Note that the following scalar example also fails:

program p
  implicit none
  integer :: k = 1
  call one (k)
contains
  subroutine one (i, j)
    integer, intent(in)           :: i
!   integer             ,optional :: j
    integer, allocatable,optional :: j
    if (present (j)) error stop "j is present"
    call two (i, j)
  end

  elemental subroutine two (i, j)
    integer, intent(in)           :: i
!   integer, value,      optional :: j
    integer, intent(in), optional :: j
    if (present (j)) error stop 99
  end
end

In subroutine one the if-statement is properly translated, but "call two"
mishandles the optional argument j when it is allocatable.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2024-01-16 22:02 ` anlauf at gcc dot gnu.org
@ 2024-01-19 18:46 ` mikael at gcc dot gnu.org
  2024-01-19 19:25 ` mikael at gcc dot gnu.org
                   ` (6 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-01-19 18:46 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #2)
> Note that adding a scalar call in function one:
> 
>     r(1) = two (i(1), j)
> 
> generates sane code:
> 
>   *((integer(kind=4) *) __result.0 + (sizetype) ((offset.1 + NON_LVALUE_EXPR
> <stride.0>) * 4)) = two (&(*i)[0], j != 0B ? *j : 0, j != 0B);
> 
> (...)
> 
> There is another observation: using the value attribute for j also in one,
> the scalar call from above becomes a straight
> 
>   *((integer(kind=4) *) __result.0 + (sizetype) ((offset.1 + NON_LVALUE_EXPR
> <stride.0>) * 4)) = two (&(*i)[0], j, .j);
> 
> while the scalarizer produces:
> 
>     integer(kind=4) * D.4340;
> ...
>     D.4340 = &j;
> ...
>           *((integer(kind=4) *) __result.0 + (sizetype) ((S.3 * D.4342 +
> D.4339) * 4)) = two (&(*i)[S.3 + -1], *D.4340);
> 
> which looks more complicated (besides being wrong...)

Wrong I agree, but is it really more complicated?


(In reply to anlauf from comment #3)
> Created attachment 57108 [details]
> Patch to play with
> 
> This is a first attempt to outline code for handling scalar dummies with the
> VALUE attribute.
> 
> This fixes the following variants of the declaration of dummy argument j
> in function one:
> 
>     integer, value,      optional :: j
>     integer, intent(in), optional :: j
>     integer, intent(in), optional :: j(4)
>     integer, intent(in), optional :: j(:)
> 
Looks promising, maybe push a fix for just these cases as a first step?

> However,
> 
>     integer, allocatable,optional :: j
> 
Allocatable AND optional?
The standard seems to accept those, but do we support them?
... (searches) ...
Alright, we have some in the testsuite.
... (searches) ...
The argument passing convention is a double pointer in this case.

> still does not work: the code *in* the generated loop looks fine to me, but
> the scalarizer dereferences j before the loop.
> 
> I think that this is correct F2018+, as ifx handles it fine.
> Not sure how to proceed here.
> 
> 
> Furthermore, the patch tries to cope (= prevent an ICE) with
> 
>     integer, allocatable,optional :: j(:)
> 
> which I think might be invalid.  At least it also crashed with ifx...
> 
There is an error to report if it's invalid, but I doubt it is.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2024-01-19 18:46 ` mikael at gcc dot gnu.org
@ 2024-01-19 19:25 ` mikael at gcc dot gnu.org
  2024-01-19 21:16 ` anlauf at gcc dot gnu.org
                   ` (5 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: mikael at gcc dot gnu.org @ 2024-01-19 19:25 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #6 from Mikael Morin <mikael at gcc dot gnu.org> ---
(In reply to anlauf from comment #4)
> 
> Note that the following scalar example also fails:
> 
"Fortunately", it is invalid.  :-)

From 15.5.2.12 (Argument presence and restrictions on arguments not present):

An optional dummy argument that is not present is subject to the following
restrictions.
(...)
  (8) If it is allocatable, it shall not be allocated, deallocated, or supplied
as an actual argument corresponding to an optional nonallocatable dummy
argument.

In comment #4, j from one is non-present, allocatable, optional and passed to j
from two which is optional nonallocatable.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2024-01-19 19:25 ` mikael at gcc dot gnu.org
@ 2024-01-19 21:16 ` anlauf at gcc dot gnu.org
  2024-01-19 21:19 ` anlauf at gcc dot gnu.org
                   ` (4 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-19 21:16 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #7 from anlauf at gcc dot gnu.org ---
(In reply to Mikael Morin from comment #6)
> (In reply to anlauf from comment #4)
> > 
> > Note that the following scalar example also fails:
> > 
> "Fortunately", it is invalid.  :-)
> 
> From 15.5.2.12 (Argument presence and restrictions on arguments not present):
> 
> An optional dummy argument that is not present is subject to the following
> restrictions.
> (...)
>   (8) If it is allocatable, it shall not be allocated, deallocated, or
> supplied as an actual argument corresponding to an optional nonallocatable
> dummy argument.
> 
> In comment #4, j from one is non-present, allocatable, optional and passed
> to j from two which is optional nonallocatable.

Thanks for clarifying this.  This helps to reduce the testcases I am looking
at.

For the next step, I've actually stepped back a little: it helps to fix
the non-elemental cases first.  I am currently working with:

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 9dd1f4086f4..52fdbd5ca66 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -6526,6 +6648,10 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
                            gfc_init_se (&argse, NULL);
                            argse.want_pointer = 1;
                            gfc_conv_expr (&argse, e);
+                           if (e->symtree->n.sym->attr.dummy
+                               && POINTER_TYPE_P (TREE_TYPE (argse.expr)))
+                             argse.expr = gfc_build_addr_expr (NULL_TREE,
+                                                               argse.expr);
                            cond = fold_convert (TREE_TYPE (argse.expr),
                                                 null_pointer_node);
                            cond = fold_build2_loc (input_location, NE_EXPR,
@@ -7256,6 +7382,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
              && e->symtree->n.sym->attr.optional
              && (((e->rank != 0 && elemental_proc)
                   || e->representation.length || e->ts.type == BT_CHARACTER
+                  || (e->rank == 0 && fsym && fsym->as == NULL)
                   || (e->rank != 0
                       && (fsym == NULL
                           || (fsym->as

I'll attach a testcase exercising this for integer dummies, but I have a
full set for other types at hand.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2024-01-19 21:16 ` anlauf at gcc dot gnu.org
@ 2024-01-19 21:19 ` anlauf at gcc dot gnu.org
  2024-01-21 20:24 ` cvs-commit at gcc dot gnu.org
                   ` (3 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-19 21:19 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from anlauf at gcc dot gnu.org ---
Created attachment 57166
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=57166&action=edit
Testcase exercising passing of integer optional dummy arguments

This testcase passes with NAG and ifx with strict checking.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2024-01-19 21:19 ` anlauf at gcc dot gnu.org
@ 2024-01-21 20:24 ` cvs-commit at gcc dot gnu.org
  2024-01-24 19:28 ` cvs-commit at gcc dot gnu.org
                   ` (2 subsequent siblings)
  11 siblings, 0 replies; 13+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2024-01-21 20:24 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #9 from GCC 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:68862e5c75ef0e875e690f0880a96fc6200d1682

commit r14-8317-g68862e5c75ef0e875e690f0880a96fc6200d1682
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Sat Jan 20 22:18:02 2024 +0100

    Fortran: passing of optional scalar arguments with VALUE attribute
[PR113377]

    gcc/fortran/ChangeLog:

            PR fortran/113377
            * trans-expr.cc (gfc_conv_procedure_call): Fix handling of optional
            scalar arguments of intrinsic type with the VALUE attribute.

    gcc/testsuite/ChangeLog:

            PR fortran/113377
            * gfortran.dg/optional_absent_9.f90: New test.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2024-01-21 20:24 ` cvs-commit at gcc dot gnu.org
@ 2024-01-24 19:28 ` cvs-commit at gcc dot gnu.org
  2024-01-25 18:26 ` anlauf at gcc dot gnu.org
  2024-01-28 19:26 ` cvs-commit at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2024-01-24 19:28 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #10 from GCC 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:186ae6d2cb93ad2e07117cff7e11def21fe285ae

commit r14-8400-g186ae6d2cb93ad2e07117cff7e11def21fe285ae
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Wed Jan 24 20:27:36 2024 +0100

    Fortran: passing of optional dummies to elemental procedures [PR113377]

    gcc/fortran/ChangeLog:

            PR fortran/113377
            * trans-expr.cc (conv_dummy_value): New.
            (gfc_conv_procedure_call): Factor code for handling dummy arguments
            with the VALUE attribute in the scalar case into
conv_dummy_value().
            Reuse and adjust for calling elemental procedures.

    gcc/testsuite/ChangeLog:

            PR fortran/113377
            * gfortran.dg/optional_absent_10.f90: New test.

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2024-01-24 19:28 ` cvs-commit at gcc dot gnu.org
@ 2024-01-25 18:26 ` anlauf at gcc dot gnu.org
  2024-01-28 19:26 ` cvs-commit at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: anlauf at gcc dot gnu.org @ 2024-01-25 18:26 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #11 from anlauf at gcc dot gnu.org ---
(In reply to GCC Commits from comment #10)
>             * gfortran.dg/optional_absent_10.f90: New test.

According to gcc-testresults this new test fails on POWER BE systems:

FAIL: gfortran.dg/optional_absent_10.f90   -O0  execution test

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

* [Bug fortran/113377] Wrong code passing optional dummy argument to elemental procedure with optional dummy
  2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2024-01-25 18:26 ` anlauf at gcc dot gnu.org
@ 2024-01-28 19:26 ` cvs-commit at gcc dot gnu.org
  11 siblings, 0 replies; 13+ messages in thread
From: cvs-commit at gcc dot gnu.org @ 2024-01-28 19:26 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #12 from GCC 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:c4773944bb3bec712b4002a2e599409301e50b11

commit r14-8479-gc4773944bb3bec712b4002a2e599409301e50b11
Author: Harald Anlauf <anlauf@gmx.de>
Date:   Thu Jan 25 22:19:10 2024 +0100

    Fortran: NULL actual to optional dummy with VALUE attribute [PR113377]

    gcc/fortran/ChangeLog:

            PR fortran/113377
            * trans-expr.cc (conv_dummy_value): Treat NULL actual argument to
            optional dummy with the VALUE attribute as not present.
            (gfc_conv_procedure_call): Likewise.

    gcc/testsuite/ChangeLog:

            PR fortran/113377
            * gfortran.dg/optional_absent_11.f90: New test.

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

end of thread, other threads:[~2024-01-28 19:26 UTC | newest]

Thread overview: 13+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2024-01-13 14:21 [Bug fortran/113377] New: Wrong code passing optional dummy argument to elemental procedure with optional dummy anlauf at gcc dot gnu.org
2024-01-14 10:51 ` [Bug fortran/113377] " mikael at gcc dot gnu.org
2024-01-14 20:05 ` anlauf at gcc dot gnu.org
2024-01-16 21:05 ` anlauf at gcc dot gnu.org
2024-01-16 22:02 ` anlauf at gcc dot gnu.org
2024-01-19 18:46 ` mikael at gcc dot gnu.org
2024-01-19 19:25 ` mikael at gcc dot gnu.org
2024-01-19 21:16 ` anlauf at gcc dot gnu.org
2024-01-19 21:19 ` anlauf at gcc dot gnu.org
2024-01-21 20:24 ` cvs-commit at gcc dot gnu.org
2024-01-24 19:28 ` cvs-commit at gcc dot gnu.org
2024-01-25 18:26 ` anlauf at gcc dot gnu.org
2024-01-28 19:26 ` cvs-commit 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).