Re: Optimization of spread

2022-11-16 Thread Théo Cavignac via Fortran
Mikael, Thomas,
Thank you very much for being so welcoming.

> The source is actually more C than C++ (the fortran front-end at least).
That's good to know, I am much more comfortable with C.

> It requires little C++ skills, but time and willingness to decipher its 
> complexity.
Yes, I don't expect that to be easy.

> There are two places where inlining can be done:
>  * In front-end passes where the parsed fortran code is rewritten
> before generating the intermediary code for the optimizers.  Thomas
> König can help you there.
>  * Directly in the code generation for the optimizers.  It is (much)
> more complex but can avoid the need for temporaries.  I can help you there.

My understanding of the compiler inner working being what it is, I
will try to have a look at the higher level side first.

> I most certainly can.  frontend-passes.cc contains, among other
> functionality, a function to inline MATMUL for small sizes, so
> much of the infrastructure is already there.
I will start my investigation there.

> > Some links about our development process and conventions:
> > https://gcc.gnu.org/contribute.html
> > https://gcc.gnu.org/git.html
>
> And, if you're into hacking gfortran, some starting pointers are at
> https://gcc.gnu.org/wiki/GFortranHacking . But always free feel to ask!
I am familiar with git, but I'll have to read the two other documents soon.

Thanks again, hopefully you'll ear about me a little later.

Best regards,
Théo

On Thu, Nov 3, 2022 at 11:04 PM Thomas Koenig  wrote:
>
> Hi,
>
> Mikael beat me to a mail saying essentially the same things by
> a few minutes, so I'm just adding a few details.
>
> > There are two places where inlining can be done:
> >   * In front-end passes where the parsed fortran code is rewritten
> > before generating the intermediary code for the optimizers.  Thomas
> > König can help you there.
>
> I most certainly can.  frontend-passes.cc contains, among other
> functionality, a function to inline MATMUL for small sizes, so
> much of the infrastructure is already there.
>
> >   * Directly in the code generation for the optimizers.  It is (much)
> > more complex but can avoid the need for temporaries.  I can help you there.
> >
> > Some links about our development process and conventions:
> > https://gcc.gnu.org/contribute.html
> > https://gcc.gnu.org/git.html
>
> And, if you're into hacking gfortran, some starting pointers are at
> https://gcc.gnu.org/wiki/GFortranHacking . But always free feel to ask!
>
> Best regards
>
> Thomas


Re: [PATCH] Fortran: ICE in simplification of array expression involving power [PR107680]

2022-11-16 Thread Mikael Morin

Le 15/11/2022 à 21:45, Harald Anlauf via Fortran a écrit :

Dear all,

when constant expressions involve parentheses, array constructors,
typespecs, and the power operator (**), we could fail with an ICE
during simplification in arith_power.

Debugging of the testcase showed we call the proper type conversions
needed for the arithmetic operation, but under certain circumstances
we seem to lose the typespec on the way to the invocation of the
simplification.  We then run into unhandled combinations of operand
types.

The attached patch is likely a sort of a band-aid to the problem:
we check the operand types in arith_power, and if we see that a
conversion is (still) needed, we punt and defer the simplification.

AFAICT this is safe.  It does not address a possibly deeply
covered issue in gfortran, which was suspected when analyzing
pr107000.  But as this is elusive, that may be hard to locate
and fix.

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


Yes, let's go with this.
Thanks for investigating.


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> 
> This patch allows the above to compile and execute.
> It has only had some light testing, and I do not know
> if nested forall and implied-do loops do work.  Feel
> free to commit as I cannot.

For nested implied-do loops, the patch appears to do
the right thing on

   program foo

  implicit none

  integer, parameter :: m = 4, n = 3
  integer k, x(m*n)

  print '(*(I0,1X))', [(i, (i*j, integer :: j=1, n), integer :: i=1, m)]
  x = [((i*j, integer :: j=1, n), integer :: i=1, m)]
  print '(*(I0,1X))', x

   end program foo

-- 
Steve


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> 
> This patch allows the above to compile and execute.
> It has only had some light testing, and I do not know
> if nested forall and implied-do loops do work.  Feel
> free to commit as I cannot.
> 

Appears to work for nested forall (at least in the execution
part of a subprogram).

! From Section 6.9 of MR&C
program foo

   implicit none

   integer, parameter :: n = 9
   integer i, j
   integer k
   integer a(n,n), b(n,n)

   a = reshape([(i,i=1,n**2)], [n,n])
   do k = 1, 9
  print '(*(I3))', a(k,:)
   end do
   print *

   b = a

   forall (i = 1:n-1)
  forall (j = i+1:n)
 a(i,j) = a(j,i) ! a is a rank-2 array
  end forall
   end forall
   do k = 1, 9
  print '(*(I3))', a(k,:)
   end do
   print *

   a = b

   forall (integer :: ii = 1:n-1)
  forall (integer :: jj = ii+1:n)
 a(ii,jj) = a(jj,ii) ! a is a rank-2 array
  end forall
   end forall
   do k = 1, 9
  print '(*(I3))', a(k,:)
   end do
   print *

end program foo

-- 
Steve


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Tue, Nov 15, 2022 at 06:31:16PM -0800, Steve Kargl via Fortran wrote:
> On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> > F2008 introduced the inclusion of a typespec in a forall
> > statement, and thn F2018 a typespec was allowed in an
> > implied-do.  There may even be a few bug reports.
> > 
> 
> Forgot to ask.  Anyone know how namespaces work with
> initialization expressions in gfortran?  This code
> should compile
> 
>program foo
>use iso_fortran_env, only : k => real_kinds
>implicit none
>integer, parameter :: n = size(k)
>integer, parameter :: &
>&  p(n) = [(precision(real(1.,k(i))), integer :: i = 1, n)]
>print '(*(I0,X))', p
>end program foo
>
> 
> The first occurence of 'i' in the expression for 'p(n)'
> is either thought to be in a different namespace, or
> an implied-do loop cannot be used in an initialization 
> expression.

After spending to much time on this, I found that decl.cc:3044-50

  m = gfc_match_init_expr (&initializer);
  if (m == MATCH_NO)
{
  gfc_error ("Expected an initialization expression at %C");
  m = MATCH_ERROR;
}

results in m == MATCH_ERROR.  First, I would expect the "if" 
condition to include the m == MATCH_ERROR to generate an
error message.  Second, an implied-do loop can appear in
an initialization expression.  So, gfortran is not handling 
this correctly.  Now, if one goes to expr.cc:gfc_match_init_expr,
gfortran matches the RHS expression, but gfc_reduce_init_expr()
fails to expand the array constructor.
-- 
Steve


Re: [PATCH] Fortran: ICE in simplification of array expression involving power [PR107680]

2022-11-16 Thread Harald Anlauf via Fortran

Am 16.11.22 um 12:39 schrieb Mikael Morin:

Le 15/11/2022 à 21:45, Harald Anlauf via Fortran a écrit :

Dear all,

when constant expressions involve parentheses, array constructors,
typespecs, and the power operator (**), we could fail with an ICE
during simplification in arith_power.

Debugging of the testcase showed we call the proper type conversions
needed for the arithmetic operation, but under certain circumstances
we seem to lose the typespec on the way to the invocation of the
simplification.  We then run into unhandled combinations of operand
types.

The attached patch is likely a sort of a band-aid to the problem:
we check the operand types in arith_power, and if we see that a
conversion is (still) needed, we punt and defer the simplification.

AFAICT this is safe.  It does not address a possibly deeply
covered issue in gfortran, which was suspected when analyzing
pr107000.  But as this is elusive, that may be hard to locate
and fix.

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


Yes, let's go with this.
Thanks for investigating.



Thanks, pushed.

I've opened a PR for the elusive loss of the typespec so that it
won't be forgotten:

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

Really a weird thing...



[PATCH] Fortran: error recovery after reference to bad CLASS variable [PR107681]

2022-11-16 Thread Harald Anlauf via Fortran
Dear all,

the attached obvious patch fixes a NULL pointer dereference
when referencing a CLASS variable with a bad decl.

Pushed as r13-4107-g96e4244ef3ccf4867ca4e37fbc6800e64ef30af6
after regtesting on x86_64-pc-linux-gnu.

Thanks,
Harald

From 96e4244ef3ccf4867ca4e37fbc6800e64ef30af6 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Wed, 16 Nov 2022 21:41:19 +0100
Subject: [PATCH] Fortran: error recovery after reference to bad CLASS variable
 [PR107681]

gcc/fortran/ChangeLog:

	PR fortran/107681
	* resolve.cc (resolve_fl_var_and_proc): Prevent NULL pointer
	dereference with reference to bad CLASS variable.

gcc/testsuite/ChangeLog:

	PR fortran/107681
	* gfortran.dg/pr107681.f90: New test.
---
 gcc/fortran/resolve.cc |  1 +
 gcc/testsuite/gfortran.dg/pr107681.f90 | 13 +
 2 files changed, 14 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/pr107681.f90

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 5ff1cd070ac..24e5aa03556 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -12967,6 +12967,7 @@ resolve_fl_var_and_proc (gfc_symbol *sym, int mp_flag)
 	  && sym->ts.u.derived
 	  && !sym->attr.select_type_temporary
 	  && !UNLIMITED_POLY (sym)
+	  && CLASS_DATA (sym)->ts.u.derived
 	  && !gfc_type_is_extensible (CLASS_DATA (sym)->ts.u.derived))
 	{
 	  gfc_error ("Type %qs of CLASS variable %qs at %L is not extensible",
diff --git a/gcc/testsuite/gfortran.dg/pr107681.f90 b/gcc/testsuite/gfortran.dg/pr107681.f90
new file mode 100644
index 000..0999ad92649
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr107681.f90
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! { dg-options "-fcoarray=lib" }
+! PR fortran/107681 - ICE in gfc_type_is_extensible
+! Contributed by G.Steinmetz
+
+program p
+  type t
+ integer, allocatable :: a
+  end type
+  class(t) :: x[*]   ! { dg-error "must be dummy, allocatable or pointer" }
+  associate (y => x) ! { dg-error "Invalid array reference" }
+  end associate
+end
--
2.35.3



Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> F2008 introduced the inclusion of a typespec in a forall
> statement, and thn F2018 a typespec was allowed in an
> implied-do.  There may even be a few bug reports.
> 

New patch.  This one handles the example of an implied-do
loop in an initialization expression (see patch for expr.cc).  


diff --git a/gcc/fortran/expr.cc b/gcc/fortran/expr.cc
index 69d0b57c688..90bd8d7251d 100644
--- a/gcc/fortran/expr.cc
+++ b/gcc/fortran/expr.cc
@@ -3165,9 +3165,20 @@ gfc_reduce_init_expr (gfc_expr *expr)
   bool t;
 
   gfc_init_expr_flag = true;
+
+  if (expr->expr_type == EXPR_ARRAY && expr->ts.type == BT_UNKNOWN)
+{
+  gfc_simplify_expr (expr, 1);
+  if (!gfc_check_constructor_type (expr))
+   return false;
+  if (!gfc_expand_constructor (expr, true))
+   return false;
+}
+
   t = gfc_resolve_expr (expr);
   if (t)
 t = gfc_check_init_expr (expr);
+
   gfc_init_expr_flag = false;
 
   if (!t || !expr)
diff --git a/gcc/fortran/match.cc b/gcc/fortran/match.cc
index 8b8b6e79c8b..3fd2a80caad 100644
--- a/gcc/fortran/match.cc
+++ b/gcc/fortran/match.cc
@@ -968,9 +968,39 @@ gfc_match_iterator (gfc_iterator *iter, int init_flag)
   gfc_expr *var, *e1, *e2, *e3;
   locus start;
   match m;
+  gfc_typespec ts;
+  bool seen_ts;
 
   e1 = e2 = e3 = NULL;
 
+  /* Match an optional "integer ::" type-spec. */
+  start = gfc_current_locus;
+  seen_ts = false;
+  gfc_clear_ts (&ts);
+  m = gfc_match_type_spec (&ts);
+  if (m == MATCH_YES)
+{
+  seen_ts = (gfc_match (" ::") == MATCH_YES);
+
+  if (seen_ts)
+   {
+ if (!gfc_notify_std (GFC_STD_F2018, "Optional type-spec "
+  "included in implied-do loop at %C"))
+   goto cleanup;
+
+ if (ts.type != BT_INTEGER)
+   {
+ gfc_error ("Type in type-spec at %C shall be INTEGER");
+ goto cleanup;
+   }
+   }
+}
+  else if (m == MATCH_ERROR)
+goto cleanup;
+
+  if (!seen_ts)
+gfc_current_locus = start;
+
   /* Match the start of an iterator without affecting the symbol table.  */
 
   start = gfc_current_locus;
@@ -984,6 +1014,14 @@ gfc_match_iterator (gfc_iterator *iter, int init_flag)
   if (m != MATCH_YES)
 return MATCH_NO;
 
+  if (seen_ts && var->ts.type == BT_UNKNOWN)
+{
+  var->ts.type = ts.type;
+  var->ts.kind = ts.kind;
+  var->symtree->n.sym->ts.type = ts.type;
+  var->symtree->n.sym->ts.kind = ts.kind;
+}
+
   if (var->symtree->n.sym->attr.dimension)
 {
   gfc_error ("Loop variable at %C cannot be an array");
@@ -2396,6 +2434,9 @@ match_forall_header (gfc_forall_iterator **phead, 
gfc_expr **mask)
   gfc_forall_iterator *head, *tail, *new_iter;
   gfc_expr *msk;
   match m;
+  locus start;
+  gfc_typespec ts;
+  bool seen_ts;
 
   gfc_gobble_whitespace ();
 
@@ -2405,12 +2446,48 @@ match_forall_header (gfc_forall_iterator **phead, 
gfc_expr **mask)
   if (gfc_match_char ('(') != MATCH_YES)
 return MATCH_NO;
 
+  /* Match an optional "integer ::" type-spec. */
+  start = gfc_current_locus;
+  seen_ts = false;
+  gfc_clear_ts (&ts);
+  m = gfc_match_type_spec (&ts);
+  if (m == MATCH_YES)
+{
+  seen_ts = (gfc_match (" ::") == MATCH_YES);
+
+  if (seen_ts)
+   {
+ if (!gfc_notify_std (GFC_STD_F2008, "Optional type-spec "
+  "included in FORALL at %C"))
+   goto cleanup;
+
+ if (ts.type != BT_INTEGER)
+   {
+ gfc_error ("Type in type-spec at %C shall be INTEGER");
+ goto cleanup;
+   }
+   }
+}
+  else if (m == MATCH_ERROR)
+goto cleanup;
+
+  if (!seen_ts)
+gfc_current_locus = start;
+
   m = match_forall_iterator (&new_iter);
   if (m == MATCH_ERROR)
 goto cleanup;
   if (m == MATCH_NO)
 goto syntax;
 
+  if (seen_ts && new_iter->var->ts.type == BT_UNKNOWN)
+{
+  new_iter->var->ts.type = ts.type;
+  new_iter->var->ts.kind = ts.kind;
+  new_iter->var->symtree->n.sym->ts.type = ts.type;
+  new_iter->var->symtree->n.sym->ts.kind = ts.kind;
+}
+
   head = tail = new_iter;
 
   for (;;)

-- 
Steve


[PATCH, committed] Fortran: ICE on procedure arguments with non-integer length [PR107707]

2022-11-16 Thread Harald Anlauf via Fortran
Dear all,

I've committed the attached patch for Steve after regtesting.
It obviously checks the types of character length to be integer
before passing them to mpz_*.

Pushed as r13-4113-gbdd784fc48a283d54f5f1e3cc2a0668c14dd3bee

Thanks,
Harald

@Steve: please close PR if you think everything is ok.

From bdd784fc48a283d54f5f1e3cc2a0668c14dd3bee Mon Sep 17 00:00:00 2001
From: Steve Kargl 
Date: Wed, 16 Nov 2022 22:46:55 +0100
Subject: [PATCH] Fortran: ICE on procedure arguments with non-integer length
 [PR107707]

gcc/fortran/ChangeLog:

	PR fortran/107707
	* interface.cc (gfc_compare_actual_formal): Check that we actually
	have integer values before asking gmp_* to use them.

gcc/testsuite/ChangeLog:

	PR fortran/107707
	* gfortran.dg/pr107707.f90: New test.
---
 gcc/fortran/interface.cc   |  2 ++
 gcc/testsuite/gfortran.dg/pr107707.f90 | 13 +
 2 files changed, 15 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/pr107707.f90

diff --git a/gcc/fortran/interface.cc b/gcc/fortran/interface.cc
index 49dbd1d886c..616ae2b1197 100644
--- a/gcc/fortran/interface.cc
+++ b/gcc/fortran/interface.cc
@@ -3273,9 +3273,11 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
   if (a->expr->ts.type == BT_CHARACTER
 	  && a->expr->ts.u.cl && a->expr->ts.u.cl->length
 	  && a->expr->ts.u.cl->length->expr_type == EXPR_CONSTANT
+	  && a->expr->ts.u.cl->length->ts.type == BT_INTEGER
 	  && f->sym->ts.type == BT_CHARACTER && f->sym->ts.u.cl
 	  && f->sym->ts.u.cl->length
 	  && f->sym->ts.u.cl->length->expr_type == EXPR_CONSTANT
+	  && f->sym->ts.u.cl->length->ts.type == BT_INTEGER
 	  && (f->sym->attr.pointer || f->sym->attr.allocatable
 	  || (f->sym->as && f->sym->as->type == AS_ASSUMED_SHAPE))
 	  && (mpz_cmp (a->expr->ts.u.cl->length->value.integer,
diff --git a/gcc/testsuite/gfortran.dg/pr107707.f90 b/gcc/testsuite/gfortran.dg/pr107707.f90
new file mode 100644
index 000..a8be2b5b299
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr107707.f90
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! PR fortran/107707 - ICE in gfc_compare_actual_formal
+! Contributed by G.Steinmetz
+
+program p
+  character(3), allocatable :: c
+  c = 'abc'
+  call s(c)
+contains
+  subroutine s(x)
+character(real(3)), allocatable :: x ! { dg-error "must be of INTEGER type" }
+  end
+end
--
2.35.3



Re: [PATCH, committed] Fortran: ICE on procedure arguments with non-integer length [PR107707]

2022-11-16 Thread Steve Kargl via Fortran
On Wed, Nov 16, 2022 at 10:58:18PM +0100, Harald Anlauf via Fortran wrote:
> 
> @Steve: please close PR if you think everything is ok.
> 

Thanks.  I'll close the pr.

-- 
Steve


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Wed, Nov 16, 2022 at 01:30:07PM -0800, Steve Kargl via Fortran wrote:
> On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> > F2008 introduced the inclusion of a typespec in a forall
> > statement, and thn F2018 a typespec was allowed in an
> > implied-do.  There may even be a few bug reports.
> > 
> 
> New patch.  This one handles the example of an implied-do
> loop in an initialization expression (see patch for expr.cc).  
> 

Seems to cause regressions.

-- 
Steve


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Wed, Nov 16, 2022 at 04:32:39PM -0800, Steve Kargl via Fortran wrote:
> On Wed, Nov 16, 2022 at 01:30:07PM -0800, Steve Kargl via Fortran wrote:
> > On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> > > F2008 introduced the inclusion of a typespec in a forall
> > > statement, and thn F2018 a typespec was allowed in an
> > > implied-do.  There may even be a few bug reports.
> > > 
> > 
> > New patch.  This one handles the example of an implied-do
> > loop in an initialization expression (see patch for expr.cc).  
> > 
> 
> Seems to cause regressions.
> 

It seems that the patch to expr.cc allows the implied-do-index
to escape into the namespace of scoping unit that contains
the implied-do loop.

-- 
Steve


Re: [PATCH 4/5] value-range: Add as_string diagnostics helper

2022-11-16 Thread Jeff Law via Fortran



On 11/12/22 16:55, Andrew Pinski via Gcc-patches wrote:

On Sat, Nov 12, 2022 at 3:47 PM Bernhard Reutner-Fischer via
Gcc-patches  wrote:

gcc/ChangeLog:

 * value-range.cc (get_bound_with_infinite_markers): New static helper.
 (irange::as_string): New definition.
 * value-range.h: New declaration.

---
Provide means to print a value range to a newly allocated buffer.
The caller is responsible to free() the allocated memory.

Bootstrapped and regtested on x86_86-unknown-linux with no regressions.
Ok for trunk?

Cc: Andrew MacLeod 
Cc: Aldy Hernandez 
---
  gcc/value-range.cc | 56 ++
  gcc/value-range.h  |  3 +++
  2 files changed, 59 insertions(+)

diff --git a/gcc/value-range.cc b/gcc/value-range.cc
index a855aaf626c..51cd9a38d90 100644
--- a/gcc/value-range.cc
+++ b/gcc/value-range.cc
@@ -3099,6 +3099,62 @@ debug (const value_range &vr)
fprintf (stderr, "\n");
  }

+/* Helper for irange::as_string().  Print a bound to an allocated buffer.  */
+static char *

Can we start using std::string instead of char* here?


If it makes the code easier to read/maintain, sure.  std::string isn't 
used heavily, but has crept into a few places, mostly in target files.  
std::string isn't something we've pushed at all in terms of preferred 
practices.



Jeff


Re: typespec in forall and implied-do

2022-11-16 Thread Steve Kargl via Fortran
On Wed, Nov 16, 2022 at 04:47:50PM -0800, Steve Kargl via Fortran wrote:
> On Wed, Nov 16, 2022 at 04:32:39PM -0800, Steve Kargl via Fortran wrote:
> > On Wed, Nov 16, 2022 at 01:30:07PM -0800, Steve Kargl via Fortran wrote:
> > > On Tue, Nov 15, 2022 at 05:13:19PM -0800, Steve Kargl via Fortran wrote:
> > > > F2008 introduced the inclusion of a typespec in a forall
> > > > statement, and thn F2018 a typespec was allowed in an
> > > > implied-do.  There may even be a few bug reports.
> > > > 
> > > 
> > > New patch.  This one handles the example of an implied-do
> > > loop in an initialization expression (see patch for expr.cc).  
> > > 
> > 
> > Seems to cause regressions.
> > 
> 
> It seems that the patch to expr.cc allows the implied-do-index
> to escape into the namespace of scoping unit that contains
> the implied-do loop.
> 

If I restrict the expr.cc patch to only kick-in when
gfc_current_ns->seen_implicit_none == 1, then there
are only 11 regression.  Perhaps, this should be committed?

-- 
Steve