[PATCH, Fortran] Diagnose default-initialized pointer/allocatable dummies

2021-09-23 Thread Sandra Loosemore
This patch is for PR101320, another issue related to missing bind(c) 
diagnostics.  OK to commit?


-Sandra
commit d3507154fd34e65e2887262218fec09d5fb082a2
Author: Sandra Loosemore 
Date:   Thu Sep 23 08:03:52 2021 -0700

Fortran: Diagnose default-initialized pointer/allocatable dummies

TS29113 changed what was then C516 in the 2010 Fortran standard (now
C1557 in F2018) from disallowing all of pointer, allocatable, and
optional attributes on dummy arguments to BIND(C) functions, to
disallowing only pointer/allocatable with default-initialization.
gfortran was previously failing to diagnose violations of this
constraint.

2021-09-23  Sandra Loosemore  

	PR Fortran/101320

	gcc/fortran/
	* decl.c (gfc_verify_c_interop_param): Handle F2018 C1557,
	aka TS29113 C516.

	gcc/testsuite/
	* gfortran.dg/c-interop/c516.f90: Remove xfails.  Add more
	tests.

diff --git a/gcc/fortran/decl.c b/gcc/fortran/decl.c
index f2e8896..b3c65b7 100644
--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -1557,6 +1557,20 @@ gfc_verify_c_interop_param (gfc_symbol *sym)
 		   "CONTIGUOUS attribute as procedure %qs is BIND(C)",
 		   sym->name, &sym->declared_at, sym->ns->proc_name->name);
 
+	  /* Per F2018, C1557, pointer/allocatable dummies to a bind(c)
+	 procedure that are default-initialized are not permitted.  */
+	  if ((sym->attr.pointer || sym->attr.allocatable)
+	  && sym->ts.type == BT_DERIVED
+	  && gfc_has_default_initializer (sym->ts.u.derived))
+	{
+	  gfc_error ("Default-initialized %s dummy argument %qs "
+			 "at %L is not permitted in BIND(C) procedure %qs",
+			 (sym->attr.pointer ? "pointer" : "allocatable"),
+			 sym->name, &sym->declared_at,
+			 sym->ns->proc_name->name);
+	  retval = false;
+	}
+
   /* Character strings are only C interoperable if they have a
 	 length of 1.  However, as an argument they are also iteroperable
 	 when passed as descriptor (which requires len=: or len=*).  */
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c516.f90 b/gcc/testsuite/gfortran.dg/c-interop/c516.f90
index 208eb84..d6a65af 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c516.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c516.f90
@@ -27,6 +27,10 @@ module m2
 
   interface
 
+! First test versions with optional attributes on the argument.
+! TS29113 removed the constraint disallowing optional arguments
+! that previously used to be in C516.
+
 ! good, no default initialization, no pointer/allocatable attribute
 subroutine s1a (x) bind (c)
   use m1
@@ -52,16 +56,54 @@ module m2
 end subroutine
 
 ! bad, default initialization + allocatable
-subroutine s2b (x) bind (c)  ! { dg-error "BIND\\(C\\)" "pr101320" { xfail *-*-* } }
+subroutine s2b (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
   use m1
   type(t2), allocatable, optional :: x
 end subroutine
 
 ! bad, default initialization + pointer
-subroutine s2c (x) bind (c)  ! { dg-error "BIND\\(C\\)" "pr101320" { xfail *-*-* } }
+subroutine s2c (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
   use m1
   type(t2), pointer, optional :: x
 end subroutine
 
+! Now do all the same tests without the optional attribute.
+
+! good, no default initialization, no pointer/allocatable attribute
+subroutine s3a (x) bind (c)
+  use m1
+  type(t1) :: x
+end subroutine
+
+! good, no default initialization
+subroutine s3b (x) bind (c)
+  use m1
+  type(t1), allocatable :: x
+end subroutine
+
+! good, no default initialization
+subroutine s3c (x) bind (c)
+  use m1
+  type(t1), pointer :: x
+end subroutine
+
+! good, default initialization but no pointer/allocatable attribute
+subroutine s4a (x) bind (c)
+  use m1
+  type(t2) :: x
+end subroutine
+
+! bad, default initialization + allocatable
+subroutine s4b (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
+  use m1
+  type(t2), allocatable :: x
+end subroutine
+
+! bad, default initialization + pointer
+subroutine s4c (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
+  use m1
+  type(t2), pointer :: x
+end subroutine
+
   end interface
 end module


Re: [PATCH, Fortran] Diagnose default-initialized pointer/allocatable dummies

2021-09-23 Thread Tobias Burnus

On 23.09.21 17:50, Sandra Loosemore wrote:

This patch is for PR101320, another issue related to missing bind(c)
diagnostics.  OK to commit?

LGTM - I am only ...

commit d3507154fd34e65e2887262218fec09d5fb082a2
Author: Sandra Loosemore
Date:   Thu Sep 23 08:03:52 2021 -0700

 Fortran: Diagnose default-initialized pointer/allocatable dummies

 TS29113 changed what was then C516 in the 2010 Fortran standard (now
 C1557 in F2018) from disallowing all of pointer, allocatable, and
 optional attributes on dummy arguments to BIND(C) functions, to
 disallowing only pointer/allocatable with default-initialization.
 gfortran was previously failing to diagnose violations of this
 constraint.

 2021-09-23  Sandra Loosemore

  PR Fortran/101320

  gcc/fortran/
  * decl.c (gfc_verify_c_interop_param): Handle F2018 C1557,
  aka TS29113 C516.

  gcc/testsuite/
  * gfortran.dg/c-interop/c516.f90: Remove xfails.  Add more
  tests.

diff --git a/gcc/fortran/decl.c b/gcc/fortran/decl.c
index f2e8896..b3c65b7 100644
--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -1557,6 +1557,20 @@ gfc_verify_c_interop_param (gfc_symbol *sym)
 "CONTIGUOUS attribute as procedure %qs is BIND(C)",
 sym->name, &sym->declared_at, sym->ns->proc_name->name);

+   /* Per F2018, C1557, pointer/allocatable dummies to a bind(c)
+  procedure that are default-initialized are not permitted.  */
+   if ((sym->attr.pointer || sym->attr.allocatable)
+   && sym->ts.type == BT_DERIVED
+   && gfc_has_default_initializer (sym->ts.u.derived))
+ {
+   gfc_error ("Default-initialized %s dummy argument %qs "
+  "at %L is not permitted in BIND(C) procedure %qs",
+  (sym->attr.pointer ? "pointer" : "allocatable"),


... wondering how to best handle such strings for translators. Namely,
whether to duplicate the string and fill-in the %s, rewriting it them to
make it clearer for the translator ("dummy argument %qs with %s
attribute"), or leaving it as is.

I think the later is acceptable – thus, I assume you will choose that
option :-)

Thanks,

Tobias



+  sym->name, &sym->declared_at,
+  sym->ns->proc_name->name);
+   retval = false;
+ }
+
/* Character strings are only C interoperable if they have a
   length of 1.  However, as an argument they are also iteroperable
   when passed as descriptor (which requires len=: or len=*).  */
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c516.f90 
b/gcc/testsuite/gfortran.dg/c-interop/c516.f90
index 208eb84..d6a65af 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c516.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c516.f90
@@ -27,6 +27,10 @@ module m2

interface

+! First test versions with optional attributes on the argument.
+! TS29113 removed the constraint disallowing optional arguments
+! that previously used to be in C516.
+
  ! good, no default initialization, no pointer/allocatable attribute
  subroutine s1a (x) bind (c)
use m1
@@ -52,16 +56,54 @@ module m2
  end subroutine

  ! bad, default initialization + allocatable
-subroutine s2b (x) bind (c)  ! { dg-error "BIND\\(C\\)" "pr101320" { xfail 
*-*-* } }
+subroutine s2b (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
use m1
type(t2), allocatable, optional :: x
  end subroutine

  ! bad, default initialization + pointer
-subroutine s2c (x) bind (c)  ! { dg-error "BIND\\(C\\)" "pr101320" { xfail 
*-*-* } }
+subroutine s2c (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
use m1
type(t2), pointer, optional :: x
  end subroutine

+! Now do all the same tests without the optional attribute.
+
+! good, no default initialization, no pointer/allocatable attribute
+subroutine s3a (x) bind (c)
+  use m1
+  type(t1) :: x
+end subroutine
+
+! good, no default initialization
+subroutine s3b (x) bind (c)
+  use m1
+  type(t1), allocatable :: x
+end subroutine
+
+! good, no default initialization
+subroutine s3c (x) bind (c)
+  use m1
+  type(t1), pointer :: x
+end subroutine
+
+! good, default initialization but no pointer/allocatable attribute
+subroutine s4a (x) bind (c)
+  use m1
+  type(t2) :: x
+end subroutine
+
+! bad, default initialization + allocatable
+subroutine s4b (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
+  use m1
+  type(t2), allocatable :: x
+end subroutine
+
+! bad, default initialization + pointer
+subroutine s4c (x) bind (c)  ! { dg-error "BIND\\(C\\)" }
+  use m1
+  type(t2), pointer :: x
+end subroutine
+
end interface
  end module

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung;

Re: [PATCH, Fortran] Diagnose default-initialized pointer/allocatable dummies

2021-09-23 Thread Sandra Loosemore

On 9/23/21 10:10 AM, Tobias Burnus wrote:

On 23.09.21 17:50, Sandra Loosemore wrote:
This patch is for PR101320, another issue related to missing bind(c) 
diagnostics.  OK to commit?

LGTM - I am only ...

diff --git a/gcc/fortran/decl.c b/gcc/fortran/decl.c
index f2e8896..b3c65b7 100644
--- a/gcc/fortran/decl.c
+++ b/gcc/fortran/decl.c
@@ -1557,6 +1557,20 @@ gfc_verify_c_interop_param (gfc_symbol *sym)
 "CONTIGUOUS attribute as procedure %qs is BIND(C)",
 sym->name, &sym->declared_at, sym->ns->proc_name->name);
+  /* Per F2018, C1557, pointer/allocatable dummies to a bind(c)
+ procedure that are default-initialized are not permitted.  */
+  if ((sym->attr.pointer || sym->attr.allocatable)
+  && sym->ts.type == BT_DERIVED
+  && gfc_has_default_initializer (sym->ts.u.derived))
+    {
+  gfc_error ("Default-initialized %s dummy argument %qs "
+ "at %L is not permitted in BIND(C) procedure %qs",
+ (sym->attr.pointer ? "pointer" : "allocatable"),


... wondering how to best handle such strings for translators. Namely, 
whether to duplicate the string and fill-in the %s, rewriting it them to 
make it clearer for the translator ("dummy argument %qs with %s 
attribute"), or leaving it as is.


I think the later is acceptable – thus, I assume you will choose that 
option :-)


Well, "pointer" and "allocatable" are Fortran language keywords, not 
just regular English words.  Should I capitalize them?  It didn't seem 
like other messages in the Fortran front end are consistent about that, 
but if that's the convention I'll do so here.


-Sandra


Re: [Patch] Fortran: Handle allocated() with coindexed scalars [PR93834] (was: [PATCH] PR fortran/93834 - [9/10/11/12 Regression] ICE in trans_caf_is_present, at fortran/trans-intrinsic.c:8469)

2021-09-23 Thread Tobias Burnus

Hi Harald,

On 22.09.21 21:47, Harald Anlauf via Fortran wrote:

while still feeling somewhat unsure (given my previous comment
and the discussion), I think your patch is basically OK.

However, your testcase has a { dg-do compile }, so it does not
really do any runtime tests.  Is that intended?  If so, please
add a respective comment, or adjust the testcase.


I have now moved the testcase to coarray/ and turned it into 'dg-do run'.

To make it a bit more interesting, I added allocate/deallocate plus some
more allocate() checks. Updating the -fdump-tree-original dump scans
took a small trickery as allocate/deallocate of a coarray has some extra
inlined checks (is allocated? did malloc work?) with -fcoarray=single
but puts the burden to the library for -fcoarray=lib. Fortunately, there
is a pointless cast for 'allocatable' which made it possible to
distinguish the ==/!= 0 checks.


Otherwise this LGTM.


Thanks for the review!

Tobias


-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955
commit 1b07d9dce6c51c98d011236c3d4cd84a2ed59ba2
Author: Tobias Burnus 
Date:   Thu Sep 23 18:47:45 2021 +0200

Fortran: Handle allocated() with coindexed scalars [PR93834]

While for an allocatable 'array', 'array(:)' and 'array(:)[1]' are
not allocatable, it is believed that not only 'scalar' but also
'scalar[1]' is allocatable.  However, coarrays are collectively
established/allocated; thus, 'allocated(scalar[i])' is equivalent
to 'allocated(scalar)'. [At least when assuming that 'i' does not
refer to a failed image.]

2021-09-23  Harald Anlauf  
Tobias Burnus  

PR fortran/93834
gcc/fortran/ChangeLog:

* trans-intrinsic.c (gfc_conv_allocated): Cleanup. Handle
coindexed scalar coarrays.

gcc/testsuite/ChangeLog:

* gfortran.dg/coarray/coarray_allocated.f90: New test.
---
 gcc/fortran/trans-intrinsic.c  | 55 +-
 .../gfortran.dg/coarray/coarray_allocated.f90  | 55 ++
 2 files changed, 89 insertions(+), 21 deletions(-)

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 42a995be348..612ca41a016 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -8887,50 +8887,63 @@ caf_this_image_ref (gfc_ref *ref)
 static void
 gfc_conv_allocated (gfc_se *se, gfc_expr *expr)
 {
-  gfc_actual_arglist *arg1;
   gfc_se arg1se;
   tree tmp;
-  symbol_attribute caf_attr;
+  bool coindexed_caf_comp = false;
+  gfc_expr *e = expr->value.function.actual->expr;
 
   gfc_init_se (&arg1se, NULL);
-  arg1 = expr->value.function.actual;
-
-  if (arg1->expr->ts.type == BT_CLASS)
+  if (e->ts.type == BT_CLASS)
 {
   /* Make sure that class array expressions have both a _data
 	 component reference and an array reference  */
-  if (CLASS_DATA (arg1->expr)->attr.dimension)
-	gfc_add_class_array_ref (arg1->expr);
+  if (CLASS_DATA (e)->attr.dimension)
+	gfc_add_class_array_ref (e);
   /*  whilst scalars only need the _data component.  */
   else
-	gfc_add_data_component (arg1->expr);
+	gfc_add_data_component (e);
 }
 
-  /* When arg1 references an allocatable component in a coarray, then call
+  /* When 'e' references an allocatable component in a coarray, then call
  the caf-library function caf_is_present ().  */
-  if (flag_coarray == GFC_FCOARRAY_LIB && arg1->expr->expr_type == EXPR_FUNCTION
-  && arg1->expr->value.function.isym
-  && arg1->expr->value.function.isym->id == GFC_ISYM_CAF_GET)
-caf_attr = gfc_caf_attr (arg1->expr->value.function.actual->expr);
-  else
-gfc_clear_attr (&caf_attr);
-  if (flag_coarray == GFC_FCOARRAY_LIB && caf_attr.codimension
-  && !caf_this_image_ref (arg1->expr->value.function.actual->expr->ref))
-tmp = trans_caf_is_present (se, arg1->expr->value.function.actual->expr);
+  if (flag_coarray == GFC_FCOARRAY_LIB && e->expr_type == EXPR_FUNCTION
+  && e->value.function.isym
+  && e->value.function.isym->id == GFC_ISYM_CAF_GET)
+{
+  e = e->value.function.actual->expr;
+  if (gfc_expr_attr (e).codimension)
+	{
+	  /* Last partref is the coindexed coarray. As coarrays are collectively
+	 (de)allocated, the allocation status must be the same as the one of
+	 the local allocation.  Convert to local access. */
+	  for (gfc_ref *ref = e->ref; ref; ref = ref->next)
+	if (ref->type == REF_ARRAY && ref->u.ar.codimen)
+	  {
+		for (int i = ref->u.ar.dimen;
+		 i < ref->u.ar.dimen + ref->u.ar.codimen; ++i)
+		ref->u.ar.dimen_type[i] = DIMEN_THIS_IMAGE;
+		break;
+	  }
+	}
+  else if (!caf_this_image_ref (e->ref))
+	coindexed_caf_comp = true;
+}
+  if (coindexed_caf_

Re: [PATCH, Fortran] Diagnose default-initialized pointer/allocatable dummies

2021-09-23 Thread Tobias Burnus

On 23.09.21 18:30, Sandra Loosemore wrote:

On 9/23/21 10:10 AM, Tobias Burnus wrote:

On 23.09.21 17:50, Sandra Loosemore wrote:

This patch is for PR101320, another issue related to missing bind(c)
diagnostics.  OK to commit?

LGTM - I am only ...

+  gfc_error ("Default-initialized %s dummy argument %qs "
+ "at %L is not permitted in BIND(C) procedure %qs",
+ (sym->attr.pointer ? "pointer" : "allocatable"),

... wondering how to best handle such strings for translators.
Namely, whether to duplicate the string and fill-in the %s, rewriting
it them to make it clearer for the translator ("dummy argument %qs
with %s attribute"), or leaving it as is.

I think the later is acceptable – thus, I assume you will choose that
option :-)


Well, "pointer" and "allocatable" are Fortran language keywords, not
just regular English words.


True but that does not solve the translator problem.

Assume the following isn't English "A %s dummy conflicts with ...", x ?
"allocatable" : "pointer"

How do you translate it? "An %s" for "An allocatable" or "A %s" for "A
pointer"? Similar issues occur all the time with languages, each having
its own special requirements.

But admittedly, there is no simple solution. In any case, I think I
wouldn't capitalize the pointer/allocatable as then those stand out -
while I think the 'default-initialized' is the more important (even
though all: it, allocatable/pointer + bind(C) are important).

And as you wrote, using %qs (%<...%>), capitalized and non-capitalized
keywords are all used a bit inconsistently.

And, as mentioned in the review, it is probably simplest to commit it as
submitted as there it no really convincing  solution to the translation
problem, I think.

Tobias

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955


[Patch] Fortran: Fix associated intrinsic with assumed rank [PR101334] [was: [PATCH, Fortran] Fixes for F2018 C838 (PR fortran/101334)]

2021-09-23 Thread Tobias Burnus

On 20.09.21 09:58, Tobias Burnus wrote:


On 20.09.21 06:01, Sandra Loosemore wrote:

This patch fixes some bugs in handling of assumed-rank arguments
revealed by the TS29113 testsuite, ... giving a bogus error when
passing one as the first argument to the ASSOCIATED intrinsic.  ...


...  if I try the following testcase, which is now permitted, I get
two ICEs. Can you check?

* The first one seems to be a bug in gfc_conv_intrinsic_function, which
  assumes also for assumed rank that if the first argument is an array,
  the second argument must also be an array.

* For the second one, I see in the dump:
p->dim[p->dtype.rank + -1].stride
  is seems as '-1' is gfc_array_index_type while 'dtype.rank' is
signed_char_type_node.


I fixed that issue + extended the testcase.

OK for mainline?

Tobias

PS: Sorry for the testcase, it should have used a separate function for
scalar vs. array target, but it somehow evolved like that.

PPS: Pending patches: (1) this one, (2) "Fortran: Improve file-reading
error diagnostic [PR55534]" (third in the series), (3) "[Patch] Fortran:
Fix assumed-size to assumed-rank passing [PR94070]" – plus (4) GFC<->CFI
array-descriptor conversion patch, but I will repost an
extended/cleaned-up version soon.

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 80634 
München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: Thomas 
Heurung, Frank Thürauf; Sitz der Gesellschaft: München; Registergericht 
München, HRB 106955
Fortran: Fix associated intrinsic with assumed rank [PR101334]

ASSOCIATE (ptr, tgt) takes as first argument also an assumed-rank array;
however, using it together with a tgt (required to be non assumed rank)
had issues for both scalar and nonscalar tgt.

	PR fortran/101334
gcc/fortran/ChangeLog:

	* trans-intrinsic.c (gfc_conv_associated): Support assumed-rank
	'pointer' with scalar/array 'target' argument.

libgfortran/ChangeLog:

	* intrinsics/associated.c (associated): Also check for same rank.

gcc/testsuite/ChangeLog:

	* gfortran.dg/associated_assumed_rank.f90: New test.

 gcc/fortran/trans-intrinsic.c  |  30 +++--
 .../gfortran.dg/associated_assumed_rank.f90| 126 +
 libgfortran/intrinsics/associated.c|   3 +-
 3 files changed, 149 insertions(+), 10 deletions(-)

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 612ca41a016..60e94f0bdc2 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -8974,7 +8974,7 @@ gfc_conv_associated (gfc_se *se, gfc_expr *expr)
   gfc_se arg2se;
   tree tmp2;
   tree tmp;
-  tree nonzero_arraylen;
+  tree nonzero_arraylen = NULL_TREE;
   gfc_ss *ss;
   bool scalar;
 
@@ -9074,14 +9074,16 @@ gfc_conv_associated (gfc_se *se, gfc_expr *expr)
 	{
 	  tmp = gfc_conv_descriptor_rank (arg1se.expr);
 	  tmp = fold_build2_loc (input_location, MINUS_EXPR,
- TREE_TYPE (tmp), tmp, gfc_index_one_node);
+ TREE_TYPE (tmp), tmp,
+ build_int_cst (TREE_TYPE (tmp), 1));
 	}
 	  else
 	tmp = gfc_rank_cst[arg1->expr->rank - 1];
 	  tmp = gfc_conv_descriptor_stride_get (arg1se.expr, tmp);
-	  nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
-	  logical_type_node, tmp,
-	  build_int_cst (TREE_TYPE (tmp), 0));
+	  if (arg2->expr->rank != 0)
+	nonzero_arraylen = fold_build2_loc (input_location, NE_EXPR,
+		logical_type_node, tmp,
+		build_int_cst (TREE_TYPE (tmp), 0));
 
 	  /* A pointer to an array, call library function _gfor_associated.  */
 	  arg1se.want_pointer = 1;
@@ -9091,16 +9093,26 @@ gfc_conv_associated (gfc_se *se, gfc_expr *expr)
 
 	  arg2se.want_pointer = 1;
 	  arg2se.force_no_tmp = 1;
-	  gfc_conv_expr_descriptor (&arg2se, arg2->expr);
+	  if (arg2->expr->rank != 0)
+	gfc_conv_expr_descriptor (&arg2se, arg2->expr);
+	  else
+	{
+	  gfc_conv_expr (&arg2se, arg2->expr);
+	  arg2se.expr
+		= gfc_conv_scalar_to_descriptor (&arg2se, arg2se.expr,
+		 gfc_expr_attr (arg2->expr));
+	  arg2se.expr = gfc_build_addr_expr (NULL_TREE, arg2se.expr);
+	}
 	  gfc_add_block_to_block (&se->pre, &arg2se.pre);
 	  gfc_add_block_to_block (&se->post, &arg2se.post);
 	  se->expr = build_call_expr_loc (input_location,
   gfor_fndecl_associated, 2,
   arg1se.expr, arg2se.expr);
 	  se->expr = convert (logical_type_node, se->expr);
-	  se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
-  logical_type_node, se->expr,
-  nonzero_arraylen);
+	  if (arg2->expr->rank != 0)
+	se->expr = fold_build2_loc (input_location, TRUTH_AND_EXPR,
+	logical_type_node, se->expr,
+	nonzero_arraylen);
 }
 
   /* If target is present zero character length pointers cannot
diff --git a/gcc/testsuite/gfortran.dg/associated_assumed_rank.f90 b/gcc/testsuite/gfortran.dg/associated_assumed_rank.f90
new file mode 100644
index 000..f1b91998006
---

[PATCH] PR fortran/102458 - ICE tree check: expected array_type, have pointer_type in gfc_conv_array_initializer, at fortran/trans-array.c:6136

2021-09-23 Thread Harald Anlauf via Fortran
Dear Fortranners,

we missed certain intrinsics as being disallowed in constant expressions,
which lead to an ICE when these intrinsics were used in a specification
expression with an initializer.  The intrinsics in question are listed in
F2018:10.1.2.

As discussed in the PR, Steve recommended to omit TRANSFER from that list,
as it is special and might need separate treatment.  I also could not come
up with a case where TRANSFER should not have simplified to a constant and
we would run into an issue.  (We could leave that job to Gerhard... ;-).

However, in testing I encountered a case involving TRANSFER that is not
properly simplified, which seems orthogonal to the present case.  I would
like to handle this separately.  This case is mentioned in the testcase,
but commented out.

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

Thanks,
Harald

Fortran - improve checking for intrinsics allowed in constant expressions

gcc/fortran/ChangeLog:

	PR fortran/102458
	* expr.c (is_non_constant_intrinsic): Check for intrinsics
	excluded in constant expressions (F2018:10.1.2).
	(gfc_is_constant_expr): Use that check.

gcc/testsuite/ChangeLog:

	PR fortran/102458
	* gfortran.dg/pr102458.f90: New test.

diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
index 604e63e6164..5ad1c4f9523 100644
--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -990,6 +990,34 @@ done:
 }


+/* Standard intrinsics listed under F2018:10.1.2 (6), which are excluded in
+   constant expressions, except TRANSFER (c.f. item (8)), which would need
+   separate treatment.  */
+
+static bool
+is_non_constant_intrinsic (gfc_expr *e)
+{
+  if (e->expr_type == EXPR_FUNCTION
+  && e->value.function.isym)
+{
+  switch (e->value.function.isym->id)
+	{
+	  case GFC_ISYM_COMMAND_ARGUMENT_COUNT:
+	  case GFC_ISYM_GET_TEAM:
+	  case GFC_ISYM_NULL:
+	  case GFC_ISYM_NUM_IMAGES:
+	  case GFC_ISYM_TEAM_NUMBER:
+	  case GFC_ISYM_THIS_IMAGE:
+	return true;
+
+	default:
+	  return false;
+	}
+}
+  return false;
+}
+
+
 /* Determine if an expression is constant in the sense of F08:7.1.12.
  * This function expects that the expression has already been simplified.  */

@@ -1023,6 +1051,10 @@ gfc_is_constant_expr (gfc_expr *e)
   gcc_assert (e->symtree || e->value.function.esym
 		  || e->value.function.isym);

+  /* Check for intrinsics excluded in constant expressions.  */
+  if (e->value.function.isym && is_non_constant_intrinsic (e))
+	return false;
+
   /* Call to intrinsic with at least one argument.  */
   if (e->value.function.isym && e->value.function.actual)
 	{
diff --git a/gcc/testsuite/gfortran.dg/pr102458.f90 b/gcc/testsuite/gfortran.dg/pr102458.f90
new file mode 100644
index 000..555e4978fdb
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr102458.f90
@@ -0,0 +1,42 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+! PR fortran/102458 - standard intrinsics excluded in constant expressions
+
+subroutine s1
+  integer :: a(command_argument_count()) = 1 ! { dg-error "Automatic array" }
+  print *, a
+end
+
+program p
+  block
+integer :: a(get_team()) = 1 ! { dg-error "Automatic array" }
+print *, a
+  end block
+end
+
+subroutine s2
+  integer :: a(num_images()) = 1 ! { dg-error "Automatic array" }
+  print *, a
+end
+
+function f()
+  block
+integer :: a(team_number()) = 0 ! { dg-error "Automatic array" }
+a = 1
+  end block
+end
+
+subroutine s3
+  integer :: a(this_image()) = 1 ! { dg-error "Automatic array" }
+  print *, a
+end
+
+subroutine s4
+  integer, parameter :: n = 4
+  integer, parameter :: x(transfer(n, n)) = 1 ! legal
+  integer:: y(transfer(n, n)) = 2 ! legal
+  integer, parameter :: k = size (x)  ! ok
+! integer, parameter :: m = size (y)  ! fails, tracked separately
+  print *, k, x, y
+  if (k /= size (y)) stop 1
+end


Re: Fortran: Improve file-reading error diagnostic [PR55534] (was: Re: [Patch] Fortran: Improve -Wmissing-include-dirs warnings [PR55534])

2021-09-23 Thread Harald Anlauf via Fortran

Hi Tobias,

Am 23.09.21 um 00:06 schrieb Tobias Burnus:

Hi Harald,

On 22.09.21 20:29, Harald Anlauf via Gcc-patches wrote:

What I find a bit confusing - from the viewpoint of a user - is the
case of using the preprocessor (-cpp), as one gets e.g.

: Warning: ./no/such/dir: No such file or directory
[-Wmissing-include-dirs]

while without -cpp:

f951: Warning: Nonexistent include directory './no/such/dir/'
[-Wmissing-include-dirs]


C/C++ do something likewise (grep for that string).

The reason for the  is the code in cpp.c's gfc_cpp_init,
which uses:
   cpp_change_file (cpp_in, LC_RENAME, _(""));

It might be possible to reset it by passing NULL to it, at the end
of that function but I don't know whether that causes side effects.
At least linemap_add then uses set->depth--.
It might work just fine, but I do not know.
(Additionally, cb_file_change or print_line needs to be updated
to handle to_file == NULL.)

Feel free to experiment there. Otherwise, I leave it as is.


I did experiment a little, trying to get something like .
Unfortunately this lead nowhere, and while I consider this
something nice-to-have, it is not important.


  * * *

However, this patch now improves the diagnostic printed by
load_file – and uses directly an fatal error instead of
a usual error and then propagating the error through.

Errors are now also properly colored.

Note:
* -fpre-included= is not easily testable. It works when calling
   the compiler itself (f951) but the driver (gfortran) overrides
   it here with:
    -fpre-include=/usr/include/finclude/math-vector-fortran.h
   which exits.

* I did not include the test "include_22.f90" with:
     include "include_22.f90"  ! { dg-error "File 'include_22.f90' is 
being included recursively" }

   as the error message seemingly confused DejaGNU and causes it
   to enter an endless loop.
 
OK for mainline?


LGTM.

Another argument for your patch series: try -fpre-include=/

* * *

There is one older issue with line numbers being off-by-one.
E.g. the testcase:

program p
  implicit none
#include "no/such/file.inc"
  type t
  end type t
end

compiled with -cpp gives:

pr55534-play.f90:4:2:

4 |   type t
  |  1~~
Fatal Error: no/such/file.inc: No such file or directory
compilation terminated.

If you have an easy solution for that one, it is pre-approved.

Thanks for the patch!

Harald


Tobias

-
Siemens Electronic Design Automation GmbH; Anschrift: Arnulfstraße 201, 
80634 München; Gesellschaft mit beschränkter Haftung; Geschäftsführer: 
Thomas Heurung, Frank Thürauf; Sitz der Gesellschaft: München; 
Registergericht München, HRB 106955





[PATCH, Fortran] Add missing diagnostic for F2018 C711 (TS29113 C407c)

2021-09-23 Thread Sandra Loosemore
Here's another missing-diagnostic patch for the Fortran front end, this 
time for PR Fortran/101333.  OK to commit?


-Sandra
commit 53171e748e28901693ca4362ff658883dab97e13
Author: Sandra Loosemore 
Date:   Thu Sep 23 15:00:43 2021 -0700

Fortran: Add missing diagnostic for F2018 C711 (TS29113 C407c)

2021-09-23  Sandra Loosemore  

	PR Fortran/101333

gcc/fortran/
	* interface.c (compare_parameter): Enforce F2018 C711.

gcc/testsuite/
	* gfortran.dg/c-interop/c407c-1.f90: Remove xfails.

diff --git a/gcc/fortran/interface.c b/gcc/fortran/interface.c
index dae4b95..a2fea0e 100644
--- a/gcc/fortran/interface.c
+++ b/gcc/fortran/interface.c
@@ -2448,6 +2448,21 @@ compare_parameter (gfc_symbol *formal, gfc_expr *actual,
   return false;
 }
 
+  /* TS29113 C407c; F2018 C711.  */
+  if (actual->ts.type == BT_ASSUMED
+  && symbol_rank (formal) == -1
+  && actual->rank != -1
+  && !(actual->symtree->n.sym->as
+	   && actual->symtree->n.sym->as->type == AS_ASSUMED_SHAPE))
+{
+  if (where)
+	gfc_error ("Assumed-type actual argument at %L corresponding to "
+		   "assumed-rank dummy argument %qs must be "
+		   "assumed-shape or assumed-rank",
+		   &actual->where, formal->name);
+  return false;
+}
+
   /* F2008, 12.5.2.5; IR F08/0073.  */
   if (formal->ts.type == BT_CLASS && formal->attr.class_ok
   && actual->expr_type != EXPR_NULL
diff --git a/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90 b/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
index e4da66a..c77e6ac 100644
--- a/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
+++ b/gcc/testsuite/gfortran.dg/c-interop/c407c-1.f90
@@ -44,7 +44,7 @@ subroutine s2 (x)
   implicit none
   type(*) :: x(*)
 
-  call g (x, 1)  ! { dg-error "Assumed.type" "pr101333" { xfail *-*-* } }
+  call g (x, 1)  ! { dg-error "Assumed.type" }
 end subroutine
 
 ! Check that a scalar gives an error.
@@ -53,7 +53,7 @@ subroutine s3 (x)
   implicit none
   type(*) :: x
 
-  call g (x, 1)  ! { dg-error "Assumed.type" "pr101333" { xfail *-*-* } }
+  call g (x, 1)  ! { dg-error "Assumed.type" }
 end subroutine
 
 ! Explicit-shape assumed-type actual arguments are forbidden implicitly


Re: [PATCH] PR fortran/102458 - ICE tree check: expected array_type, have pointer_type in gfc_conv_array_initializer, at fortran/trans-array.c:6136

2021-09-23 Thread Jerry D via Fortran

Harald,

Looks good. OK and thanks for your time and efforts.

Jerry

On 9/23/21 12:47 PM, Harald Anlauf via Fortran wrote:

Dear Fortranners,

we missed certain intrinsics as being disallowed in constant expressions,
which lead to an ICE when these intrinsics were used in a specification
expression with an initializer.  The intrinsics in question are listed in
F2018:10.1.2.

As discussed in the PR, Steve recommended to omit TRANSFER from that list,
as it is special and might need separate treatment.  I also could not come
up with a case where TRANSFER should not have simplified to a constant and
we would run into an issue.  (We could leave that job to Gerhard... ;-).

However, in testing I encountered a case involving TRANSFER that is not
properly simplified, which seems orthogonal to the present case.  I would
like to handle this separately.  This case is mentioned in the testcase,
but commented out.

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

Thanks,
Harald