Re: [Backport gcc-11, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2022-02-14 Thread Andre Vehreschild via Gcc-patches
Hi everyone,

sorry for missing out on the gcc-11 backport, but better late than never. 

Committed backport as ae57aae60d1.

Regards,
Andre

On Wed, 23 Jun 2021 11:21:45 +0200
Tobias Burnus  wrote:

> On 23.06.21 10:23, Andre Vehreschild wrote:
> 
> > Will wait two weeks for any errors introduced by this patch before
> > backporting to gcc-11, ok?  
> 
> Fine with me.
> 
> Thanks again for the patch.
> 
> Tobias
> 
> -
> Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank
> Thürauf


-- 
Andre Vehreschild * Email: vehre ad gmx dot de 


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-23 Thread Tobias Burnus

On 23.06.21 10:23, Andre Vehreschild wrote:


Will wait two weeks for any errors introduced by this patch before backporting
to gcc-11, ok?


Fine with me.

Thanks again for the patch.

Tobias

-
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München 
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank 
Thürauf


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-23 Thread Andre Vehreschild via Gcc-patches
Hi all,

the fix for PR100337 was submitted as da13e4ebebb07a47d5fb50eab8893f8fe38683df.

Thanks for the review Tobias.

@Tobias: You are right, caf_single does not get much testing. But this part
(not providing a stat) is tested multiple times, because of the laziness. Nearly
none of the tests in the testsuite provides a variable for stat.

Will wait two weeks for any errors introduced by this patch before backporting
to gcc-11, ok?

Regards,
Andre

On Tue, 22 Jun 2021 10:37:27 +0200
Tobias Burnus  wrote:

> Hi Andre,
> 
> On 22.06.21 09:40, Andre Vehreschild via Fortran wrote:
> > To the questions:
> > - I added a test only for -fcoarray=single because in the library case the
> >optional stat is just propagated to the library, which is already tested
> > a lot of times and which needs to handle the optional stat in any case. So
> > an error there would have been detected in one of the earlier tests. I did
> > not want to add unnecessary  test overhead given that the tests already run
> > for a long time.  
> Fair point.
> > - I did not add tests for the other CO_* routines, i.e. CO_MIN, CO_MAX,
> >CO_REDUCE or CO_SUM, that are also handled by this routine, because I
> > believe that showing that the fix works for CO_BROADCAST shows that the
> > others work, too. Because the four others do not have any special handling
> > in their implementation in  trans_intrinsic. Or do you mean other
> > coarray-routines besides the five handled by conv_co_collective()?  
> Well, that relates more to the first point – for -fcoarray=lib, it
> likely makes a difference. For -fcoarray=single not. If the former is
> skipped, it is much less relevant for the second.
> > If it is ok for you, I would apply the patch as is, or do you see a reason
> > to add more tests?  
> 
> OK.
> 
> Although, I am not that sure that libcaf_single gets that much testing.
> On the other hand, -fcoarray=lib with -lcaf_single is also not that
> relevant in the real world, either.
> 
> Tobias
> 
> -
> Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank
> Thürauf


-- 
Andre Vehreschild * Email: vehre ad gmx dot de 


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-22 Thread Tobias Burnus

Hi Andre,

On 22.06.21 09:40, Andre Vehreschild via Fortran wrote:

To the questions:
- I added a test only for -fcoarray=single because in the library case the
   optional stat is just propagated to the library, which is already tested a
   lot of times and which needs to handle the optional stat in any case. So an
   error there would have been detected in one of the earlier tests. I did not
   want to add unnecessary  test overhead given that the tests already run for a
   long time.

Fair point.

- I did not add tests for the other CO_* routines, i.e. CO_MIN, CO_MAX,
   CO_REDUCE or CO_SUM, that are also handled by this routine, because I believe
   that showing that the fix works for CO_BROADCAST shows that the others work,
   too. Because the four others do not have any special handling in their
   implementation in  trans_intrinsic. Or do you mean other coarray-routines
   besides the five handled by conv_co_collective()?

Well, that relates more to the first point – for -fcoarray=lib, it
likely makes a difference. For -fcoarray=single not. If the former is
skipped, it is much less relevant for the second.

If it is ok for you, I would apply the patch as is, or do you see a reason to
add more tests?


OK.

Although, I am not that sure that libcaf_single gets that much testing.
On the other hand, -fcoarray=lib with -lcaf_single is also not that
relevant in the real world, either.

Tobias

-
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München 
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank 
Thürauf


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-22 Thread Andre Vehreschild via Gcc-patches
Hi Tobias,

thanks for the review.

To the questions: 

- I added a test only for -fcoarray=single because in the library case the
  optional stat is just propagated to the library, which is already tested a
  lot of times and which needs to handle the optional stat in any case. So an
  error there would have been detected in one of the earlier tests. I did not
  want to add unnecessary  test overhead given that the tests already run for a
  long time.

- I did not add tests for the other CO_* routines, i.e. CO_MIN, CO_MAX,
  CO_REDUCE or CO_SUM, that are also handled by this routine, because I believe
  that showing that the fix works for CO_BROADCAST shows that the others work,
  too. Because the four others do not have any special handling in their
  implementation in  trans_intrinsic. Or do you mean other coarray-routines
  besides the five handled by conv_co_collective()?

If it is ok for you, I would apply the patch as is, or do you see a reason to
add more tests?

Regards,
Andre

On Mon, 21 Jun 2021 14:30:21 +0200
Tobias Burnus  wrote:

> Any reason that you did not put it under
>gfortran.dg/coarray/
> such that it is also run with -fcoarray=lib (-lcaf_single)?
> I know that the issue only exists for single, but it also makes
> sense to check that libcaf_single works 
> 
> In that sense, I wonder whether also the other CO_* should be
> checked in the testsuite as they are handled differently in
> libcaf_... (but identical with -fcoarray=single).
> 
> Except for those two nits, it LGTM. Thanks!
> 
> Tobias
> 
> PS: The function is used by
>  case GFC_ISYM_CO_BROADCAST:
>  case GFC_ISYM_CO_MIN:
>  case GFC_ISYM_CO_MAX:
>  case GFC_ISYM_CO_REDUCE:
>  case GFC_ISYM_CO_SUM:
> and, with -fcoarray=single, errmsg is not touched
> as stat is (unconditionally) 0 (success)..
> 
> 
> On 19.06.21 13:23, Andre Vehreschild via Fortran wrote:
> > PING!
> >
> > On Fri, 4 Jun 2021 18:05:18 +0200
> > Andre Vehreschild  wrote:
> >  
> >> Ping!
> >>
> >> On Fri, 21 May 2021 15:33:11 +0200
> >> Andre Vehreschild  wrote:
> >>  
> >>> Hi,
> >>>
> >>> the attached patch fixes an issue when calling CO_BROADCAST in
> >>> -fcoarray=single mode, where the optional but non-present (in the calling
> >>> scope) stat variable was assigned to before checking for it being not
> >>> present.
> >>>
> >>> Regtests fine on x86-64-linux/f33. Ok for trunk?
> >>>
> >>> Regards,
> >>> Andre  
> >>  
> >
> > --
> > Andre Vehreschild * Email: vehre ad gmx dot de  
> -
> Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München
> Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank
> Thürauf


-- 
Andre Vehreschild * Email: vehre ad gmx dot de 


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-21 Thread Tobias Burnus

Any reason that you did not put it under
  gfortran.dg/coarray/
such that it is also run with -fcoarray=lib (-lcaf_single)?
I know that the issue only exists for single, but it also makes
sense to check that libcaf_single works 

In that sense, I wonder whether also the other CO_* should be
checked in the testsuite as they are handled differently in
libcaf_... (but identical with -fcoarray=single).

Except for those two nits, it LGTM. Thanks!

Tobias

PS: The function is used by
case GFC_ISYM_CO_BROADCAST:
case GFC_ISYM_CO_MIN:
case GFC_ISYM_CO_MAX:
case GFC_ISYM_CO_REDUCE:
case GFC_ISYM_CO_SUM:
and, with -fcoarray=single, errmsg is not touched
as stat is (unconditionally) 0 (success)..


On 19.06.21 13:23, Andre Vehreschild via Fortran wrote:

PING!

On Fri, 4 Jun 2021 18:05:18 +0200
Andre Vehreschild  wrote:


Ping!

On Fri, 21 May 2021 15:33:11 +0200
Andre Vehreschild  wrote:


Hi,

the attached patch fixes an issue when calling CO_BROADCAST in
-fcoarray=single mode, where the optional but non-present (in the calling
scope) stat variable was assigned to before checking for it being not
present.

Regtests fine on x86-64-linux/f33. Ok for trunk?

Regards,
Andre




--
Andre Vehreschild * Email: vehre ad gmx dot de

-
Mentor Graphics (Deutschland) GmbH, Arnulfstrasse 201, 80634 München 
Registergericht München HRB 106955, Geschäftsführer: Thomas Heurung, Frank 
Thürauf


Re: [Ping^2, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-19 Thread Andre Vehreschild via Gcc-patches
PING!

On Fri, 4 Jun 2021 18:05:18 +0200
Andre Vehreschild  wrote:

> Ping!
>
> On Fri, 21 May 2021 15:33:11 +0200
> Andre Vehreschild  wrote:
>
> > Hi,
> >
> > the attached patch fixes an issue when calling CO_BROADCAST in
> > -fcoarray=single mode, where the optional but non-present (in the calling
> > scope) stat variable was assigned to before checking for it being not
> > present.
> >
> > Regtests fine on x86-64-linux/f33. Ok for trunk?
> >
> > Regards,
> > Andre
>
>


--
Andre Vehreschild * Email: vehre ad gmx dot de
gcc/fortran/ChangeLog:

	PR fortran/100337
	* trans-intrinsic.c (conv_co_collective): Check stat for null ptr
	before dereferrencing.

gcc/testsuite/ChangeLog:

	PR fortran/100337
	* gfortran.dg/coarray_collectives_17.f90: New test.

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 4d7451479d3..03a38090051 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -11232,8 +11232,28 @@ conv_co_collective (gfc_code *code)
   if (flag_coarray == GFC_FCOARRAY_SINGLE)
 {
   if (stat != NULL_TREE)
-	gfc_add_modify (, stat,
-			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	{
+	  /* For optional stats, check the pointer is valid before zero'ing.  */
+	  if (gfc_expr_attr (stat_expr).optional)
+	{
+	  tree tmp;
+	  stmtblock_t ass_block;
+	  gfc_start_block (_block);
+	  gfc_add_modify (_block, stat,
+			  fold_convert (TREE_TYPE (stat),
+	integer_zero_node));
+	  tmp = fold_build2 (NE_EXPR, logical_type_node,
+ gfc_build_addr_expr (NULL_TREE, stat),
+ null_pointer_node);
+	  tmp = fold_build3 (COND_EXPR, void_type_node, tmp,
+ gfc_finish_block (_block),
+ build_empty_stmt (input_location));
+	  gfc_add_expr_to_block (, tmp);
+	}
+	  else
+	gfc_add_modify (, stat,
+			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	}
   return gfc_finish_block ();
 }

diff --git a/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90 b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
new file mode 100644
index 000..84a6645865e
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
@@ -0,0 +1,42 @@
+! { dg-do run }
+! { dg-options "-fcoarray=single" }
+!
+! PR 100337
+! Test case inspired by code submitted by Brad Richardson
+
+program main
+implicit none
+
+integer, parameter :: MESSAGE = 42
+integer :: result
+
+call myco_broadcast(MESSAGE, result, 1)
+
+if (result /= MESSAGE) error stop 1
+contains
+subroutine myco_broadcast(m, r, source_image, stat, errmsg)
+integer, intent(in) :: m
+integer, intent(out) :: r
+integer, intent(in) :: source_image
+integer, intent(out), optional :: stat
+character(len=*), intent(inout), optional :: errmsg
+
+integer :: data_length
+
+data_length = 1
+
+call co_broadcast(data_length, source_image, stat, errmsg)
+
+if (present(stat)) then
+if (stat /= 0) return
+end if
+
+if (this_image() == source_image) then
+r = m
+end if
+
+call co_broadcast(r, source_image, stat, errmsg)
+end subroutine
+
+end program
+


[Ping, Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-06-04 Thread Andre Vehreschild via Gcc-patches
Ping!

On Fri, 21 May 2021 15:33:11 +0200
Andre Vehreschild  wrote:

> Hi,
>
> the attached patch fixes an issue when calling CO_BROADCAST in
> -fcoarray=single mode, where the optional but non-present (in the calling
> scope) stat variable was assigned to before checking for it being not present.
>
> Regtests fine on x86-64-linux/f33. Ok for trunk?
>
> Regards,
>   Andre


--
Andre Vehreschild * Email: vehre ad gmx dot de
gcc/fortran/ChangeLog:

	PR fortran/100337
	* trans-intrinsic.c (conv_co_collective): Check stat for null ptr
	before dereferrencing.

gcc/testsuite/ChangeLog:

	PR fortran/100337
	* gfortran.dg/coarray_collectives_17.f90: New test.

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 4d7451479d3..03a38090051 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -11232,8 +11232,28 @@ conv_co_collective (gfc_code *code)
   if (flag_coarray == GFC_FCOARRAY_SINGLE)
 {
   if (stat != NULL_TREE)
-	gfc_add_modify (, stat,
-			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	{
+	  /* For optional stats, check the pointer is valid before zero'ing.  */
+	  if (gfc_expr_attr (stat_expr).optional)
+	{
+	  tree tmp;
+	  stmtblock_t ass_block;
+	  gfc_start_block (_block);
+	  gfc_add_modify (_block, stat,
+			  fold_convert (TREE_TYPE (stat),
+	integer_zero_node));
+	  tmp = fold_build2 (NE_EXPR, logical_type_node,
+ gfc_build_addr_expr (NULL_TREE, stat),
+ null_pointer_node);
+	  tmp = fold_build3 (COND_EXPR, void_type_node, tmp,
+ gfc_finish_block (_block),
+ build_empty_stmt (input_location));
+	  gfc_add_expr_to_block (, tmp);
+	}
+	  else
+	gfc_add_modify (, stat,
+			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	}
   return gfc_finish_block ();
 }

diff --git a/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90 b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
new file mode 100644
index 000..84a6645865e
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
@@ -0,0 +1,42 @@
+! { dg-do run }
+! { dg-options "-fcoarray=single" }
+!
+! PR 100337
+! Test case inspired by code submitted by Brad Richardson
+
+program main
+implicit none
+
+integer, parameter :: MESSAGE = 42
+integer :: result
+
+call myco_broadcast(MESSAGE, result, 1)
+
+if (result /= MESSAGE) error stop 1
+contains
+subroutine myco_broadcast(m, r, source_image, stat, errmsg)
+integer, intent(in) :: m
+integer, intent(out) :: r
+integer, intent(in) :: source_image
+integer, intent(out), optional :: stat
+character(len=*), intent(inout), optional :: errmsg
+
+integer :: data_length
+
+data_length = 1
+
+call co_broadcast(data_length, source_image, stat, errmsg)
+
+if (present(stat)) then
+if (stat /= 0) return
+end if
+
+if (this_image() == source_image) then
+r = m
+end if
+
+call co_broadcast(r, source_image, stat, errmsg)
+end subroutine
+
+end program
+


[Patch, Fortran] PR100337 Should be able to pass non-present optional arguments to CO_BROADCAST

2021-05-21 Thread Andre Vehreschild via Gcc-patches
Hi,

the attached patch fixes an issue when calling CO_BROADCAST in -fcoarray=single
mode, where the optional but non-present (in the calling scope) stat variable
was assigned to before checking for it being not present.

Regtests fine on x86-64-linux/f33. Ok for trunk?

Regards,
Andre
--
Andre Vehreschild * Email: vehre ad gmx dot de
gcc/fortran/ChangeLog:

	PR fortran/100337
	* trans-intrinsic.c (conv_co_collective): Check stat for null ptr
	before dereferrencing.

gcc/testsuite/ChangeLog:

	PR fortran/100337
	* gfortran.dg/coarray_collectives_17.f90: New test.

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 4d7451479d3..03a38090051 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -11232,8 +11232,28 @@ conv_co_collective (gfc_code *code)
   if (flag_coarray == GFC_FCOARRAY_SINGLE)
 {
   if (stat != NULL_TREE)
-	gfc_add_modify (, stat,
-			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	{
+	  /* For optional stats, check the pointer is valid before zero'ing.  */
+	  if (gfc_expr_attr (stat_expr).optional)
+	{
+	  tree tmp;
+	  stmtblock_t ass_block;
+	  gfc_start_block (_block);
+	  gfc_add_modify (_block, stat,
+			  fold_convert (TREE_TYPE (stat),
+	integer_zero_node));
+	  tmp = fold_build2 (NE_EXPR, logical_type_node,
+ gfc_build_addr_expr (NULL_TREE, stat),
+ null_pointer_node);
+	  tmp = fold_build3 (COND_EXPR, void_type_node, tmp,
+ gfc_finish_block (_block),
+ build_empty_stmt (input_location));
+	  gfc_add_expr_to_block (, tmp);
+	}
+	  else
+	gfc_add_modify (, stat,
+			fold_convert (TREE_TYPE (stat), integer_zero_node));
+	}
   return gfc_finish_block ();
 }

diff --git a/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90 b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
new file mode 100644
index 000..84a6645865e
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/coarray_collectives_17.f90
@@ -0,0 +1,42 @@
+! { dg-do run }
+! { dg-options "-fcoarray=single" }
+!
+! PR 100337
+! Test case inspired by code submitted by Brad Richardson
+
+program main
+implicit none
+
+integer, parameter :: MESSAGE = 42
+integer :: result
+
+call myco_broadcast(MESSAGE, result, 1)
+
+if (result /= MESSAGE) error stop 1
+contains
+subroutine myco_broadcast(m, r, source_image, stat, errmsg)
+integer, intent(in) :: m
+integer, intent(out) :: r
+integer, intent(in) :: source_image
+integer, intent(out), optional :: stat
+character(len=*), intent(inout), optional :: errmsg
+
+integer :: data_length
+
+data_length = 1
+
+call co_broadcast(data_length, source_image, stat, errmsg)
+
+if (present(stat)) then
+if (stat /= 0) return
+end if
+
+if (this_image() == source_image) then
+r = m
+end if
+
+call co_broadcast(r, source_image, stat, errmsg)
+end subroutine
+
+end program
+