public inbox for fortran@gcc.gnu.org
 help / color / mirror / Atom feed
* [PATCH] PR/101135 - Load of null pointer when passing absent assumed-shape array argument for an optional dummy argument
@ 2022-01-29 21:41 Harald Anlauf
  2022-02-04 10:45 ` Mikael Morin
  0 siblings, 1 reply; 7+ messages in thread
From: Harald Anlauf @ 2022-01-29 21:41 UTC (permalink / raw)
  To: fortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 1783 bytes --]

Dear Fortranners,

compiling with -fsanitize=undefined shows that we did mishandle the
case where a missing optional argument is passed to another procedure.

Besides the example given in the PR, the existing testcase
fortran.dg/missing_optional_dummy_6a.f90 fails with:

gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:21:29: runtime error: load of null pointer of type 'integer(kind=4)'
gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:22:30: runtime error: load of null pointer of type 'integer(kind=4)'
gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:27:29: runtime error: load of null pointer of type 'integer(kind=4)'

The least invasive change - already pointed out by the reporter - is
to check the presence of the argument before dereferencing the data
pointer after the offset calculation.  This requires adjusting the
checking pattern for gfortran.dg/missing_optional_dummy_6a.f90.

Regtesting reminded me that procedures with bind(c) attribute are doing
their own stuff, which is why they need to be excluded here, otherwise
testcase bind-c-contiguous-4.f90 would regress on the expected output.

I've created a testcase that uses this PR's input as well as the lesson
learned from studying the bind(c) testcase and placed this in the asan
subdirectory.

There is a potential alternative solution which I did not pursue, as I
think it is more invasive, but also that I didn't succeed to implement:
A non-present dummy array argument should not need to get its descriptor
set up.  Pursuing this is probably not the right thing to do during the
current stage of development and could be implemented later.  If somebody
believes this is important, feel free to open a PR for this.

Regtested on x86_64-pc-linux-gnu.  OK for mainline?

Thanks,
Harald


[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: 0001-Fortran-fix-handling-of-absent-array-argument-passed.patch --]
[-- Type: text/x-patch, Size: 5326 bytes --]

From 69ca8f83149107f48b86360eb878d9d746b99234 Mon Sep 17 00:00:00 2001
From: Harald Anlauf <anlauf@gmx.de>
Date: Sat, 29 Jan 2022 22:18:30 +0100
Subject: [PATCH] Fortran: fix handling of absent array argument passed to
 optional dummy

gcc/fortran/ChangeLog:

	PR fortran/101135
	* trans-array.cc (gfc_get_dataptr_offset): Check for optional
	arguments being present before dereferencing data pointer.

gcc/testsuite/ChangeLog:

	PR fortran/101135
	* gfortran.dg/missing_optional_dummy_6a.f90: Adjust diagnostic patterns.
	* gfortran.dg/asan/missing_optional_dummy_7.f90: New test.
---
 gcc/fortran/trans-array.cc                    | 11 ++++
 .../asan/missing_optional_dummy_7.f90         | 64 +++++++++++++++++++
 .../gfortran.dg/missing_optional_dummy_6a.f90 |  4 +-
 3 files changed, 77 insertions(+), 2 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/asan/missing_optional_dummy_7.f90

diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
index cfb6eac11c7..9eaa99c5550 100644
--- a/gcc/fortran/trans-array.cc
+++ b/gcc/fortran/trans-array.cc
@@ -7207,6 +7207,17 @@ gfc_get_dataptr_offset (stmtblock_t *block, tree parm, tree desc, tree offset,

   /* Set the target data pointer.  */
   offset = gfc_build_addr_expr (gfc_array_dataptr_type (desc), tmp);
+
+  /* Check for optional dummy argument being present.  BIND(C) procedure
+     arguments are excepted here since they are handled differently.  */
+  if (expr->expr_type == EXPR_VARIABLE
+      && expr->symtree->n.sym->attr.dummy
+      && expr->symtree->n.sym->attr.optional
+      && !expr->symtree->n.sym->ns->proc_name->attr.is_bind_c)
+    offset = build3_loc (input_location, COND_EXPR, TREE_TYPE (offset),
+			 gfc_conv_expr_present (expr->symtree->n.sym), offset,
+			 fold_convert (TREE_TYPE (offset), gfc_index_zero_node));
+
   gfc_conv_descriptor_data_set (block, parm, offset);
 }

diff --git a/gcc/testsuite/gfortran.dg/asan/missing_optional_dummy_7.f90 b/gcc/testsuite/gfortran.dg/asan/missing_optional_dummy_7.f90
new file mode 100644
index 00000000000..bdd7006170d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/asan/missing_optional_dummy_7.f90
@@ -0,0 +1,64 @@
+! { dg-do run }
+! { dg-additional-options "-fdump-tree-original -fsanitize=undefined" }
+!
+! PR fortran/101135 - Load of null pointer when passing absent
+! assumed-shape array argument for an optional dummy argument
+!
+! Based on testcase by Marcel Jacobse
+
+program main
+  implicit none
+  character(len=3) :: a(6) = ['abc', 'def', 'ghi', 'jlm', 'nop', 'qrs']
+  call as ()
+  call as (a(::2))
+  call as_c ()
+  call as_c (a(2::2))
+  call test_wrapper
+  call test_wrapper_c
+  call test2_wrapper
+contains
+  subroutine as (xx)
+    character(len=*), optional, intent(in) :: xx(*)
+    if (.not. present (xx)) return
+    print *, xx(1:3)
+  end subroutine as
+  subroutine as_c (zz) bind(c)
+    character(len=*), optional, intent(in) :: zz(*)
+    if (.not. present (zz)) return
+    print *, zz(1:3)
+  end subroutine as_c
+
+  subroutine test_wrapper (x)
+    real, dimension(1), intent(out), optional :: x
+    call test (x) !
+  end subroutine test_wrapper
+  subroutine test (y)
+    real, dimension(:), intent(out), optional :: y
+    if (present (y)) y=0
+  end subroutine test
+
+  subroutine test_wrapper_c (w) bind(c)
+    real, dimension(1), intent(out), optional :: w
+    call test_c (w)
+  end subroutine test_wrapper_c
+  subroutine test_c (y) bind(c)
+    real, dimension(:), intent(out), optional :: y
+    if (present (y)) y=0
+  end subroutine test_c
+
+  subroutine test2_wrapper (u, v)
+    real,               intent(out), optional :: u
+    real, dimension(1), intent(out), optional :: v
+    call test2 (u)
+    call test2 (v) !
+  end subroutine test2_wrapper
+  subroutine test2 (z)
+    real, dimension(..), intent(out), optional :: z
+  end subroutine test2
+end program
+
+! { dg-final { scan-tree-dump-times "data = v != 0B " 1 "original" } }
+! { dg-final { scan-tree-dump-times "data = x != 0B " 1 "original" } }
+! { dg-final { scan-tree-dump-times "data = xx.0 != 0B " 1 "original" } }
+! { dg-output " abcghinop(\n|\r\n|\r)" }"
+! { dg-output " defjlmqrs(\n|\r\n|\r)" }"
diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
index c08c97a2c7e..bd34613c143 100644
--- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
+++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
@@ -49,10 +49,10 @@ end program test

 ! { dg-final { scan-tree-dump-times "scalar2 \\(slr1" 1 "original" } }

-! { dg-final { scan-tree-dump-times "= es1 != 0B" 1 "original" } }
+! { dg-final { scan-tree-dump-times "= es1 != 0B" 2 "original" } }
 ! { dg-final { scan-tree-dump-times "assumed_shape2 \\(es1" 0 "original" } }
 ! { dg-final { scan-tree-dump-times "explicit_shape2 \\(es1" 1 "original" } }

-! { dg-final { scan-tree-dump-times "= as1.0 != 0B" 2 "original" } }
+! { dg-final { scan-tree-dump-times "= as1.0 != 0B" 4 "original" } }
 ! { dg-final { scan-tree-dump-times "assumed_shape2 \\(as1" 0 "original" } }
 ! { dg-final { scan-tree-dump-times "explicit_shape2 \\(as1" 0 "original" } }
--
2.31.1


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

* Re: [PATCH] PR/101135 - Load of null pointer when passing absent assumed-shape array argument for an optional dummy argument
  2022-01-29 21:41 [PATCH] PR/101135 - Load of null pointer when passing absent assumed-shape array argument for an optional dummy argument Harald Anlauf
@ 2022-02-04 10:45 ` Mikael Morin
  2022-02-06 21:04   ` Harald Anlauf
  0 siblings, 1 reply; 7+ messages in thread
From: Mikael Morin @ 2022-02-04 10:45 UTC (permalink / raw)
  To: Harald Anlauf, fortran, gcc-patches

Hello,

Le 29/01/2022 à 22:41, Harald Anlauf via Fortran a écrit :
> Dear Fortranners,
> 
> compiling with -fsanitize=undefined shows that we did mishandle the
> case where a missing optional argument is passed to another procedure.
> 
> Besides the example given in the PR, the existing testcase
> fortran.dg/missing_optional_dummy_6a.f90 fails with:
> 
> gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:21:29: runtime error: load of null pointer of type 'integer(kind=4)'
> gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:22:30: runtime error: load of null pointer of type 'integer(kind=4)'
> gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90:27:29: runtime error: load of null pointer of type 'integer(kind=4)'
> 
> The least invasive change - already pointed out by the reporter - is
> to check the presence of the argument before dereferencing the data
> pointer after the offset calculation.  This requires adjusting the
> checking pattern for gfortran.dg/missing_optional_dummy_6a.f90.
> 
> Regtesting reminded me that procedures with bind(c) attribute are doing
> their own stuff, which is why they need to be excluded here, otherwise
> testcase bind-c-contiguous-4.f90 would regress on the expected output.
> 
> I've created a testcase that uses this PR's input as well as the lesson
> learned from studying the bind(c) testcase and placed this in the asan
> subdirectory.
> 
> There is a potential alternative solution which I did not pursue, as I
> think it is more invasive, but also that I didn't succeed to implement:
> A non-present dummy array argument should not need to get its descriptor
> set up.  Pursuing this is probably not the right thing to do during the
> current stage of development and could be implemented later.  If somebody
> believes this is important, feel free to open a PR for this.
> 
I have an other (equally unimportant) concern that it may create an 
unnecessary conditional when passing a subobject of an optional 
argument.  In that case we can assume that the optional is present.
It’s not a correctness issue, so let’s not bother at this stage.

> Regtested on x86_64-pc-linux-gnu.  OK for mainline?
> 
OK.

Thanks.

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

* Re: [PATCH] PR/101135 - Load of null pointer when passing absent assumed-shape array argument for an optional dummy argument
  2022-02-04 10:45 ` Mikael Morin
@ 2022-02-06 21:04   ` Harald Anlauf
  2024-03-15 19:32     ` [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135] Harald Anlauf
  0 siblings, 1 reply; 7+ messages in thread
From: Harald Anlauf @ 2022-02-06 21:04 UTC (permalink / raw)
  To: Mikael Morin, fortran, gcc-patches

Hi Mikael,

Am 04.02.22 um 11:45 schrieb Mikael Morin:
> Hello,
>
> Le 29/01/2022 à 22:41, Harald Anlauf via Fortran a écrit :
>> The least invasive change - already pointed out by the reporter - is
>> to check the presence of the argument before dereferencing the data
>> pointer after the offset calculation.  This requires adjusting the
>> checking pattern for gfortran.dg/missing_optional_dummy_6a.f90.
>>
>> Regtesting reminded me that procedures with bind(c) attribute are doing
>> their own stuff, which is why they need to be excluded here, otherwise
>> testcase bind-c-contiguous-4.f90 would regress on the expected output.

only after submitting the patch I figured that the patch is incomplete.

When we have a call chain of procedures with and without bind(c),
there are still cases left where the failure with the sanitizer
is not fixed.  Just add "bind(c)" to subroutine test_wrapper only
in the original PR.

I have added a corresponding comment in the PR.

>> There is a potential alternative solution which I did not pursue, as I
>> think it is more invasive, but also that I didn't succeed to implement:
>> A non-present dummy array argument should not need to get its descriptor
>> set up.  Pursuing this is probably not the right thing to do during the
>> current stage of development and could be implemented later.  If somebody
>> believes this is important, feel free to open a PR for this.
>>
> I have an other (equally unimportant) concern that it may create an
> unnecessary conditional when passing a subobject of an optional
> argument.  In that case we can assume that the optional is present.
> It’s not a correctness issue, so let’s not bother at this stage.

Judging from the dump tree of the cases I looked at I did not see
anything that would pose a problem to the optimizer.

>> Regtested on x86_64-pc-linux-gnu.  OK for mainline?
>>
> OK.

Given my latest observations I'd rather withdraw the current version of
the patch and rethink.  I also did not see an issue with bind(c)
procedures calling alikes.

It would help if one would not only know the properties of the actual
argument, but also of the formal one, which is not available at that
point in the code.  I'll have another look and resubmit.

> Thanks.
>

Thanks for the review!

Harald


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

* [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135]
  2022-02-06 21:04   ` Harald Anlauf
@ 2024-03-15 19:32     ` Harald Anlauf
  2024-03-17 21:04       ` Mikael Morin
  0 siblings, 1 reply; 7+ messages in thread
From: Harald Anlauf @ 2024-03-15 19:32 UTC (permalink / raw)
  To: Mikael Morin, fortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 3251 bytes --]

Dear all,

as there has been some good progress in the handling of optional dummy
arguments, I looked again at this PR and a patch for it that I withdrew
as it turned out incomplete.

It turned out that it now needs only a minor adjustment for optional
dummy arguments of procedures with bind(c) attribute so that ubsan
checking does not trigger.

Along this way I extended the previous testcase to exercise to some
extent combinations of bind(c) and non-bind(c) procedures and found
one failure (since at least gcc-9) that is genuine: passing a missing
optional from a bind(c) procedure to an assumed-rank dummy, see
PR114355.  The corresponding test is commented in the testcase.

Regtested on x86_64-pc-linux-gnu.  OK for mainline?

Thanks,
Harald


On 2/6/22 22:04, Harald Anlauf wrote:
> Hi Mikael,
>
> Am 04.02.22 um 11:45 schrieb Mikael Morin:
>> Hello,
>>
>> Le 29/01/2022 à 22:41, Harald Anlauf via Fortran a écrit :
>>> The least invasive change - already pointed out by the reporter - is
>>> to check the presence of the argument before dereferencing the data
>>> pointer after the offset calculation.  This requires adjusting the
>>> checking pattern for gfortran.dg/missing_optional_dummy_6a.f90.
>>>
>>> Regtesting reminded me that procedures with bind(c) attribute are doing
>>> their own stuff, which is why they need to be excluded here, otherwise
>>> testcase bind-c-contiguous-4.f90 would regress on the expected output.
>
> only after submitting the patch I figured that the patch is incomplete.
>
> When we have a call chain of procedures with and without bind(c),
> there are still cases left where the failure with the sanitizer
> is not fixed.  Just add "bind(c)" to subroutine test_wrapper only
> in the original PR.
>
> I have added a corresponding comment in the PR.
>
>>> There is a potential alternative solution which I did not pursue, as I
>>> think it is more invasive, but also that I didn't succeed to implement:
>>> A non-present dummy array argument should not need to get its descriptor
>>> set up.  Pursuing this is probably not the right thing to do during the
>>> current stage of development and could be implemented later.  If
>>> somebody
>>> believes this is important, feel free to open a PR for this.
>>>
>> I have an other (equally unimportant) concern that it may create an
>> unnecessary conditional when passing a subobject of an optional
>> argument.  In that case we can assume that the optional is present.
>> It’s not a correctness issue, so let’s not bother at this stage.
>
> Judging from the dump tree of the cases I looked at I did not see
> anything that would pose a problem to the optimizer.
>
>>> Regtested on x86_64-pc-linux-gnu.  OK for mainline?
>>>
>> OK.
>
> Given my latest observations I'd rather withdraw the current version of
> the patch and rethink.  I also did not see an issue with bind(c)
> procedures calling alikes.
>
> It would help if one would not only know the properties of the actual
> argument, but also of the formal one, which is not available at that
> point in the code.  I'll have another look and resubmit.
>
>> Thanks.
>>
>
> Thanks for the review!
>
> Harald
>

[-- Attachment #2: pr101135-v2.diff --]
[-- Type: text/x-patch, Size: 6171 bytes --]

From b3079a82a220477704f8156207239e4af4103ea9 Mon Sep 17 00:00:00 2001
From: Harald Anlauf <anlauf@gmx.de>
Date: Fri, 15 Mar 2024 20:14:07 +0100
Subject: [PATCH] Fortran: fix for absent array argument passed to optional
 dummy [PR101135]

gcc/fortran/ChangeLog:

	PR fortran/101135
	* trans-array.cc (gfc_get_dataptr_offset): Check for optional
	arguments being present before dereferencing data pointer.

gcc/testsuite/ChangeLog:

	PR fortran/101135
	* gfortran.dg/missing_optional_dummy_6a.f90: Adjust diagnostic pattern.
	* gfortran.dg/ubsan/missing_optional_dummy_8.f90: New test.
---
 gcc/fortran/trans-array.cc                    |  11 ++
 .../gfortran.dg/missing_optional_dummy_6a.f90 |   2 +-
 .../ubsan/missing_optional_dummy_8.f90        | 108 ++++++++++++++++++
 3 files changed, 120 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/ubsan/missing_optional_dummy_8.f90

diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
index 3673fa40720..a7717a8107e 100644
--- a/gcc/fortran/trans-array.cc
+++ b/gcc/fortran/trans-array.cc
@@ -7526,6 +7526,17 @@ gfc_get_dataptr_offset (stmtblock_t *block, tree parm, tree desc, tree offset,
 
   /* Set the target data pointer.  */
   offset = gfc_build_addr_expr (gfc_array_dataptr_type (desc), tmp);
+
+  /* Check for optional dummy argument being present.  Arguments of BIND(C)
+     procedures are excepted here since they are handled differently.  */
+  if (expr->expr_type == EXPR_VARIABLE
+      && expr->symtree->n.sym->attr.dummy
+      && expr->symtree->n.sym->attr.optional
+      && !is_CFI_desc (NULL, expr))
+    offset = build3_loc (input_location, COND_EXPR, TREE_TYPE (offset),
+			 gfc_conv_expr_present (expr->symtree->n.sym), offset,
+			 fold_convert (TREE_TYPE (offset), gfc_index_zero_node));
+
   gfc_conv_descriptor_data_set (block, parm, offset);
 }
 
diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
index c6a79059a91..b5e1726d74d 100644
--- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
+++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_6a.f90
@@ -49,7 +49,7 @@ end program test
 
 ! { dg-final { scan-tree-dump-times "scalar2 \\(.* slr1" 1 "original" } }
 
-! { dg-final { scan-tree-dump-times "= es1 != 0B" 1 "original" } }
+! { dg-final { scan-tree-dump-times "= es1 != 0B" 2 "original" } }
 ! { dg-final { scan-tree-dump-times "assumed_shape2 \\(es1" 0 "original" } }
 ! { dg-final { scan-tree-dump-times "explicit_shape2 \\(es1" 1 "original" } }
 
diff --git a/gcc/testsuite/gfortran.dg/ubsan/missing_optional_dummy_8.f90 b/gcc/testsuite/gfortran.dg/ubsan/missing_optional_dummy_8.f90
new file mode 100644
index 00000000000..fd3914934aa
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/ubsan/missing_optional_dummy_8.f90
@@ -0,0 +1,108 @@
+! { dg-do run }
+! { dg-additional-options "-fdump-tree-original -fsanitize=undefined" }
+!
+! PR fortran/101135 - Load of null pointer when passing absent
+! assumed-shape array argument for an optional dummy argument
+!
+! Based on testcase by Marcel Jacobse
+
+program main
+  implicit none
+  character(len=3) :: a(6) = ['abc', 'def', 'ghi', 'jlm', 'nop', 'qrs']
+  call as ()
+  call as (a(::2))
+  call as_c ()
+  call as_c (a(2::2))
+  call test_wrapper
+  call test_wrapper_c
+  call test_ar_wrapper
+  call test_ar_wrapper_c
+contains
+  subroutine as (xx)
+    character(len=*), optional, intent(in) :: xx(*)
+    if (.not. present (xx)) return
+    print *, xx(1:3)
+  end subroutine as
+
+  subroutine as_c (zz) bind(c)
+    character(len=*), optional, intent(in) :: zz(*)
+    if (.not. present (zz)) return
+    print *, zz(1:3)
+  end subroutine as_c
+
+  subroutine test_wrapper (x)
+    real, dimension(1), intent(out), optional :: x
+    call test (x)
+    call test1 (x)
+    call test_c (x)
+    call test1_c (x)
+  end subroutine test_wrapper
+
+  subroutine test_wrapper_c (w) bind(c)
+    real, dimension(1), intent(out), optional :: w
+    call test (w)
+    call test1 (w)
+    call test_c (w)
+    call test1_c (w)
+  end subroutine test_wrapper_c
+
+  subroutine test (y)
+    real, dimension(:), intent(out), optional :: y
+    if (present (y)) y=0.
+  end subroutine test
+
+  subroutine test_c (y) bind(c)
+    real, dimension(:), intent(out), optional :: y
+    if (present (y)) y=0.
+  end subroutine test_c
+
+  subroutine test1 (y)
+    real, dimension(1), intent(out), optional :: y
+    if (present (y)) y=0.
+  end subroutine test1
+
+  subroutine test1_c (y) bind(c)
+    real, dimension(1), intent(out), optional :: y
+    if (present (y)) y=0.
+  end subroutine test1_c
+
+  subroutine test_ar_wrapper (p, q, r)
+    real,               intent(out), optional :: p
+    real, dimension(1), intent(out), optional :: q
+    real, dimension(:), intent(out), optional :: r
+    call test_ar (p)
+    call test_ar (q)
+    call test_ar (r)
+    call test_ar_c (p)
+    call test_ar_c (q)
+    call test_ar_c (r)
+  end subroutine test_ar_wrapper
+
+  subroutine test_ar_wrapper_c (u, v, s) bind(c)
+    real,               intent(out), optional :: u
+    real, dimension(1), intent(out), optional :: v
+    real, dimension(:), intent(out), optional :: s
+    call test_ar (u)
+    call test_ar (v)
+!   call test_ar (s)    ! Disabled due to runtime segfault, see pr114355
+    call test_ar_c (u)
+    call test_ar_c (v)
+    call test_ar_c (s)
+  end subroutine test_ar_wrapper_c
+
+  subroutine test_ar (z)
+    real, dimension(..), intent(out), optional :: z
+  end subroutine test_ar
+
+  subroutine test_ar_c (z) bind(c)
+    real, dimension(..), intent(out), optional :: z
+  end subroutine test_ar_c
+end program
+
+! { dg-final { scan-tree-dump-times "data = v != 0B " 2 "original" } }
+! { dg-final { scan-tree-dump-times "data = w != 0B " 2 "original" } }
+! { dg-final { scan-tree-dump-times "data = q != 0B " 2 "original" } }
+! { dg-final { scan-tree-dump-times "data = x != 0B " 2 "original" } }
+! { dg-final { scan-tree-dump-times "data = xx.0 != 0B " 1 "original" } }
+! { dg-output " abcghinop(\n|\r\n|\r)" }"
+! { dg-output " defjlmqrs(\n|\r\n|\r)" }"
-- 
2.35.3


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

* Re: [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135]
  2024-03-15 19:32     ` [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135] Harald Anlauf
@ 2024-03-17 21:04       ` Mikael Morin
  2024-03-17 22:10         ` Harald Anlauf
  0 siblings, 1 reply; 7+ messages in thread
From: Mikael Morin @ 2024-03-17 21:04 UTC (permalink / raw)
  To: Harald Anlauf, fortran, gcc-patches

Le 15/03/2024 à 20:32, Harald Anlauf a écrit :
> Dear all,
> 
> as there has been some good progress in the handling of optional dummy
> arguments, I looked again at this PR and a patch for it that I withdrew
> as it turned out incomplete.
> 
> It turned out that it now needs only a minor adjustment for optional
> dummy arguments of procedures with bind(c) attribute so that ubsan
> checking does not trigger.
> 
> Along this way I extended the previous testcase to exercise to some
> extent combinations of bind(c) and non-bind(c) procedures and found
> one failure (since at least gcc-9) that is genuine: passing a missing
> optional from a bind(c) procedure to an assumed-rank dummy, see
> PR114355.  The corresponding test is commented in the testcase.
> 
> Regtested on x86_64-pc-linux-gnu.  OK for mainline?
> 
> Thanks,
> Harald
> 
(...)
> 
> From b3079a82a220477704f8156207239e4af4103ea9 Mon Sep 17 00:00:00 2001
> From: Harald Anlauf <anlauf@gmx.de>
> Date: Fri, 15 Mar 2024 20:14:07 +0100
> Subject: [PATCH] Fortran: fix for absent array argument passed to optional
>  dummy [PR101135]
> 
> gcc/fortran/ChangeLog:
> 
> 	PR fortran/101135
> 	* trans-array.cc (gfc_get_dataptr_offset): Check for optional
> 	arguments being present before dereferencing data pointer.
> 
> gcc/testsuite/ChangeLog:
> 
> 	PR fortran/101135
> 	* gfortran.dg/missing_optional_dummy_6a.f90: Adjust diagnostic pattern.
> 	* gfortran.dg/ubsan/missing_optional_dummy_8.f90: New test.
> ---
>  gcc/fortran/trans-array.cc                    |  11 ++
>  .../gfortran.dg/missing_optional_dummy_6a.f90 |   2 +-
>  .../ubsan/missing_optional_dummy_8.f90        | 108 ++++++++++++++++++
>  3 files changed, 120 insertions(+), 1 deletion(-)
>  create mode 100644 gcc/testsuite/gfortran.dg/ubsan/missing_optional_dummy_8.f90
> 
> diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
> index 3673fa40720..a7717a8107e 100644
> --- a/gcc/fortran/trans-array.cc
> +++ b/gcc/fortran/trans-array.cc
> @@ -7526,6 +7526,17 @@ gfc_get_dataptr_offset (stmtblock_t *block, tree parm, tree desc, tree offset,
>  
>    /* Set the target data pointer.  */
>    offset = gfc_build_addr_expr (gfc_array_dataptr_type (desc), tmp);
> +
> +  /* Check for optional dummy argument being present.  Arguments of BIND(C)
> +     procedures are excepted here since they are handled differently.  */
> +  if (expr->expr_type == EXPR_VARIABLE
> +      && expr->symtree->n.sym->attr.dummy
> +      && expr->symtree->n.sym->attr.optional
> +      && !is_CFI_desc (NULL, expr))

I think the condition could additionally check the lack of subreferences.
But it's maybe not worth the trouble, and the patch is conservatively 
correct as is, so OK.

Thanks for the patch.

> +    offset = build3_loc (input_location, COND_EXPR, TREE_TYPE (offset),
> +			 gfc_conv_expr_present (expr->symtree->n.sym), offset,
> +			 fold_convert (TREE_TYPE (offset), gfc_index_zero_node));
> +
>    gfc_conv_descriptor_data_set (block, parm, offset);
>  }
>  


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

* Re: [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135]
  2024-03-17 21:04       ` Mikael Morin
@ 2024-03-17 22:10         ` Harald Anlauf
  2024-03-18 18:47           ` Mikael Morin
  0 siblings, 1 reply; 7+ messages in thread
From: Harald Anlauf @ 2024-03-17 22:10 UTC (permalink / raw)
  To: Mikael Morin, fortran, gcc-patches

Hi Mikael,

On 3/17/24 22:04, Mikael Morin wrote:
>> diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
>> index 3673fa40720..a7717a8107e 100644
>> --- a/gcc/fortran/trans-array.cc
>> +++ b/gcc/fortran/trans-array.cc
>> @@ -7526,6 +7526,17 @@ gfc_get_dataptr_offset (stmtblock_t *block,
>> tree parm, tree desc, tree offset,
>>
>>    /* Set the target data pointer.  */
>>    offset = gfc_build_addr_expr (gfc_array_dataptr_type (desc), tmp);
>> +
>> +  /* Check for optional dummy argument being present.  Arguments of
>> BIND(C)
>> +     procedures are excepted here since they are handled
>> differently.  */
>> +  if (expr->expr_type == EXPR_VARIABLE
>> +      && expr->symtree->n.sym->attr.dummy
>> +      && expr->symtree->n.sym->attr.optional
>> +      && !is_CFI_desc (NULL, expr))
>
> I think the condition could additionally check the lack of subreferences.
> But it's maybe not worth the trouble, and the patch is conservatively
> correct as is, so OK.

I have thought about the conditions here for some time and did not
find better ones.  They need to be broad enough to catch the case
in gfortran.dg/missing_optional_dummy_6a.f90 that (according to the
tree-dump) was not properly handled previously and would have triggered
ubsan at some point in the future when someone tried to change that
testcase from currently dg-do compile to dg-do run...
(After the patch it would pass, but I didn't dare to change the dg-do).

I have pushed the patch as-is, but feel free to post testcases
not covered (or improperly covered) to narrow this down further...

> Thanks for the patch.

Thanks for the review!

Harald

>> +    offset = build3_loc (input_location, COND_EXPR, TREE_TYPE (offset),
>> +             gfc_conv_expr_present (expr->symtree->n.sym), offset,
>> +             fold_convert (TREE_TYPE (offset), gfc_index_zero_node));
>> +
>>    gfc_conv_descriptor_data_set (block, parm, offset);
>>  }
>>
>
>


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

* Re: [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135]
  2024-03-17 22:10         ` Harald Anlauf
@ 2024-03-18 18:47           ` Mikael Morin
  0 siblings, 0 replies; 7+ messages in thread
From: Mikael Morin @ 2024-03-18 18:47 UTC (permalink / raw)
  To: Harald Anlauf, fortran, gcc-patches

Le 17/03/2024 à 23:10, Harald Anlauf a écrit :
> Hi Mikael,
> 
> On 3/17/24 22:04, Mikael Morin wrote:
>>> diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
>>> index 3673fa40720..a7717a8107e 100644
>>> --- a/gcc/fortran/trans-array.cc
>>> +++ b/gcc/fortran/trans-array.cc
>>> @@ -7526,6 +7526,17 @@ gfc_get_dataptr_offset (stmtblock_t *block,
>>> tree parm, tree desc, tree offset,
>>>
>>>    /* Set the target data pointer.  */
>>>    offset = gfc_build_addr_expr (gfc_array_dataptr_type (desc), tmp);
>>> +
>>> +  /* Check for optional dummy argument being present.  Arguments of
>>> BIND(C)
>>> +     procedures are excepted here since they are handled
>>> differently.  */
>>> +  if (expr->expr_type == EXPR_VARIABLE
>>> +      && expr->symtree->n.sym->attr.dummy
>>> +      && expr->symtree->n.sym->attr.optional
>>> +      && !is_CFI_desc (NULL, expr))
>>
>> I think the condition could additionally check the lack of subreferences.
>> But it's maybe not worth the trouble, and the patch is conservatively
>> correct as is, so OK.
> 
> I have thought about the conditions here for some time and did not
> find better ones.  They need to be broad enough to catch the case
> in gfortran.dg/missing_optional_dummy_6a.f90 that (according to the
> tree-dump) was not properly handled previously and would have triggered
> ubsan at some point in the future when someone tried to change that
> testcase from currently dg-do compile to dg-do run...

No problem, as said it is conservatively correct.

> (After the patch it would pass, but I didn't dare to change the dg-do).
> Did it include cases not covered by the new testcase (which was quite 
complete already)?

> I have pushed the patch as-is, but feel free to post testcases
> not covered (or improperly covered) to narrow this down further...
> 
The case I had in mind would only be a missed optimization, and probably 
not that important, so let's move on.

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

end of thread, other threads:[~2024-03-18 18:47 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2022-01-29 21:41 [PATCH] PR/101135 - Load of null pointer when passing absent assumed-shape array argument for an optional dummy argument Harald Anlauf
2022-02-04 10:45 ` Mikael Morin
2022-02-06 21:04   ` Harald Anlauf
2024-03-15 19:32     ` [PATCH, v2] Fortran: fix for absent array argument passed to optional dummy [PR101135] Harald Anlauf
2024-03-17 21:04       ` Mikael Morin
2024-03-17 22:10         ` Harald Anlauf
2024-03-18 18:47           ` Mikael Morin

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).