Re: [PATCH, v2] Fortran: improve attribute conflict checking [PR93635]

2024-05-24 Thread Harald Anlauf

Hi Mikael,

On 5/24/24 20:17, Mikael Morin wrote:

Le 23/05/2024 à 21:15, Harald Anlauf a écrit :

Hi Mikael,

On 5/23/24 09:49, Mikael Morin wrote:

Le 13/05/2024 à 09:25, Mikael Morin a écrit :

Le 10/05/2024 à 21:56, Harald Anlauf a écrit :

Am 10.05.24 um 21:48 schrieb Harald Anlauf:

Hi Mikael,

Am 10.05.24 um 11:45 schrieb Mikael Morin:

Le 09/05/2024 à 22:30, Harald Anlauf a écrit :

I'll stop here...


Thanks. Go figure, I have no problem reproducing today.
It's PR99798 (and there is even a patch for it).


this patch has rotten a bit: the type of gfc_reluease_symbol
has changed to bool, this can be fixed.

Unfortunately, applying the patch does not remove the ICEs here...


Oops, I take that back!  There was an error on my side applying the
patch; and now it does fix the ICEs after correcting that hickup


Now the PR99798 patch is ready to be pushed, but I won't be available
for a few days.  We can finish our discussion on this topic afterwards.


Hello,

I'm coming back to this.
I think either one of Steve's patch or your variant in the PR is a
better fix for the ICE as a first step; they seem less fragile at least.
Then we can look at a possible reordering of conflict checks as with the
patch you originally submitted in this thread.


like the attached variant?


Yes.  The churn in the testsuite is actually not that bad.
OK for master, thanks for the patch.


thanks, will do.

I wouldn't push for backporting, but if you feel like doing it, it seems 
safe enough (depending on my own backport for PR99798 of course).


There's no pressing need.  I'll mark the patch as backportable
with dependency in my own list, in case the question comes up.

Regarding the conflict check reordering, I'm tempted to just drop it at 
this point, or do you think it remains worth it?


I don't really have a showcase where this would bring a benefit now,
so I'm dropping this idea.

There are issues where specifying a standard version changes
the error recovery path (or rather lead to an ICE), but as some
of these are due to emitting an error during parsing instead of
during resolution, my suggestion does not help there.

If you look for an example: this one is taken from pr101281

subroutine a3pr (xn) bind(C)
  character(len=n), pointer :: xn(..)
end

vs.

subroutine a3pr (xn) bind(C)
  character(len=n), pointer :: xn
  dimension :: xn(..)
end

The first one gives lots of invalid reads in valgrind with -std=f2008,
or ICEs, while the second does not.

Thanks,
Harald




Re: [Patch, PR Fortran/90069] Polymorphic Return Type Memory Leak Without Intermediate Variable

2024-05-28 Thread Harald Anlauf

Hi Andre,

On 5/28/24 14:10, Andre Vehreschild wrote:

Hi all,

the attached patch fixes a memory leak with unlimited polymorphic return types.
The leak occurred, because an expression with side-effects was evaluated twice.
I have substituted the check for non-variable expressions followed by creating a
SAVE_EXPR with checking for trees with side effects and creating temp. variable
and freeing the memory.


this looks good to me.  It also solves the runtime memory leak in
testcase pr114012.f90 .  Nice!


Btw, I do not get the SAVE_EXPR in the old code. Is there something missing to
manifest it or is a SAVE_EXPR not meant to be evaluated twice?


I was assuming that the comment in gcc/tree.h applies here:

/* save_expr (EXP) returns an expression equivalent to EXP
   but it can be used multiple times within context CTX
   and only evaluate EXP once.  */

I do not know what the practical difference between a SAVE_EXPR
and a temporary explicitly evaluated once (which you have now)
is, except that you can free the temporary cleanly.


Anyway, regtested ok on Linux-x86_64-Fedora_39. Ok for master?


Yes, this is fine from my side.  If you are inclined to backport
to e.g. 14-branch after a grace period, that would be great.


This work is funded by the Souvereign Tech Fund. Yes, the funding has been
granted and Nicolas, Mikael and me will be working on some Fortran topics in
the next 12-18 months.


This is really great news!


Regards,
Andre


Thanks for the patch!

Harald


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




Re: [PATCH 03/52] fortran: Replace uses of {FLOAT, {, LONG_}DOUBLE}_TYPE_SIZE

2024-06-03 Thread Harald Anlauf

Hi,

Am 03.06.24 um 05:00 schrieb Kewen Lin:

Joseph pointed out "floating types should have their mode,
not a poorly defined precision value" in the discussion[1],
as he and Richi suggested, the existing macros
{FLOAT,{,LONG_}DOUBLE}_TYPE_SIZE will be replaced with a
hook mode_for_floating_type.  To be prepared for that, this
patch is to replace use of {FLOAT,{,LONG_}DOUBLE}_TYPE_SIZE
in fortran with TYPE_PRECISION of
{float,{,long_}double}_type_node.

[1] https://gcc.gnu.org/pipermail/gcc-patches/2024-May/651209.html

gcc/fortran/ChangeLog:

* trans-intrinsic.cc (build_round_expr): Use TYPE_PRECISION of
long_double_type_node to replace LONG_DOUBLE_TYPE_SIZE.
* trans-types.cc (gfc_build_real_type): Use TYPE_PRECISION of
{float,double,long_double}_type_node to replace
{FLOAT,DOUBLE,LONG_DOUBLE}_TYPE_SIZE.
---
  gcc/fortran/trans-intrinsic.cc |  3 ++-
  gcc/fortran/trans-types.cc | 10 ++
  2 files changed, 8 insertions(+), 5 deletions(-)

diff --git a/gcc/fortran/trans-intrinsic.cc b/gcc/fortran/trans-intrinsic.cc
index 912c1000e18..96839705112 100644
--- a/gcc/fortran/trans-intrinsic.cc
+++ b/gcc/fortran/trans-intrinsic.cc
@@ -395,7 +395,8 @@ build_round_expr (tree arg, tree restype)
   don't have an appropriate function that converts directly to the integer
   type (such as kind == 16), just use ROUND, and then convert the result to
   an integer.  We might also need to convert the result afterwards.  */
-  if (resprec <= INT_TYPE_SIZE && argprec <= LONG_DOUBLE_TYPE_SIZE)
+  if (resprec <= INT_TYPE_SIZE
+  && argprec <= TYPE_PRECISION (long_double_type_node))
  fn = builtin_decl_for_precision (BUILT_IN_IROUND, argprec);
else if (resprec <= LONG_TYPE_SIZE)
  fn = builtin_decl_for_precision (BUILT_IN_LROUND, argprec);
diff --git a/gcc/fortran/trans-types.cc b/gcc/fortran/trans-types.cc
index 8466c595e06..0ef67723fcd 100644
--- a/gcc/fortran/trans-types.cc
+++ b/gcc/fortran/trans-types.cc
@@ -873,13 +873,15 @@ gfc_build_real_type (gfc_real_info *info)
int mode_precision = info->mode_precision;
tree new_type;

-  if (mode_precision == FLOAT_TYPE_SIZE)
+  if (mode_precision == TYPE_PRECISION (float_type_node))
  info->c_float = 1;
-  if (mode_precision == DOUBLE_TYPE_SIZE)
+  if (mode_precision == TYPE_PRECISION (double_type_node))
  info->c_double = 1;
-  if (mode_precision == LONG_DOUBLE_TYPE_SIZE && !info->c_float128)
+  if (mode_precision == TYPE_PRECISION (long_double_type_node)
+  && !info->c_float128)
  info->c_long_double = 1;
-  if (mode_precision != LONG_DOUBLE_TYPE_SIZE && mode_precision == 128)
+  if (mode_precision != TYPE_PRECISION (long_double_type_node)
+  && mode_precision == 128)
  {
/* TODO: see PR101835.  */
info->c_float128 = 1;


the Fortran part looks good to me.

Thanks,
Harald



[PATCH] Fortran: fix ALLOCATE with SOURCE=, zero-length character [PR83865]

2024-06-03 Thread Harald Anlauf
Dear all,

the attached simple patch fixes an ICE for ALLOCATE with SOURCE=
of a deferred-length character array with source-expression
being an array of character with length zero.  The reason was
that the array descriptor of the source-expression was discarded
in the special case of length 0.

Solution: restrict special case to rank 0.

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

The offending code was introduced during 7-development,
so it is technically a regression.  I would therefore
like to backport after waiting for a week or two.

Thanks,
Harald
From ae5e3654d30d17584cfcfc3bbcc48cf75cb7453c Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Mon, 3 Jun 2024 22:02:06 +0200
Subject: [PATCH] Fortran: fix ALLOCATE with SOURCE=, zero-length character
 [PR83865]

gcc/fortran/ChangeLog:

	PR fortran/83865
	* trans-stmt.cc (gfc_trans_allocate): Restrict special case for
	source-expression with zero-length character to rank 0, so that
	the array shape is not discarded.

gcc/testsuite/ChangeLog:

	PR fortran/83865
	* gfortran.dg/allocate_with_source_32.f90: New test.
---
 gcc/fortran/trans-stmt.cc |  3 +-
 .../gfortran.dg/allocate_with_source_32.f90   | 33 +++
 2 files changed, 35 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/allocate_with_source_32.f90

diff --git a/gcc/fortran/trans-stmt.cc b/gcc/fortran/trans-stmt.cc
index 9b497d6bdc6..93b633e212e 100644
--- a/gcc/fortran/trans-stmt.cc
+++ b/gcc/fortran/trans-stmt.cc
@@ -6449,8 +6449,9 @@ gfc_trans_allocate (gfc_code * code, gfc_omp_namelist *omp_allocate)
   else
 	gfc_add_block_to_block (&post, &se.post);

-  /* Special case when string in expr3 is zero.  */
+  /* Special case when string in expr3 is scalar and has length zero.  */
   if (code->expr3->ts.type == BT_CHARACTER
+	  && code->expr3->rank == 0
 	  && integer_zerop (se.string_length))
 	{
 	  gfc_init_se (&se, NULL);
diff --git a/gcc/testsuite/gfortran.dg/allocate_with_source_32.f90 b/gcc/testsuite/gfortran.dg/allocate_with_source_32.f90
new file mode 100644
index 000..4a9bd46da4d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/allocate_with_source_32.f90
@@ -0,0 +1,33 @@
+! { dg-do run }
+!
+! PR fortran/83865
+!
+! Test ALLOCATE with SOURCE= of deferred length character, where
+! the source-expression is an array of character with length 0.
+
+program p
+  implicit none
+  character(:), allocatable :: z(:)
+  character(1) :: cc(4) = ""
+  allocate (z, source=[''])
+  if (len (z) /= 0 .or. size (z) /= 1) stop 1
+  deallocate (z)
+  allocate (z, source=['',''])
+  if (len (z) /= 0 .or. size (z) /= 2) stop 2
+  deallocate (z)
+  allocate (z, source=[ character(0) :: 'a','b','c'])
+  if (len (z) /= 0 .or. size (z) /= 3) stop 3
+  deallocate (z)
+  allocate (z, source=[ character(0) :: cc ])
+  if (len (z) /= 0 .or. size (z) /= 4) stop 4
+  deallocate (z)
+  associate (x => f())
+if (len (x) /= 0 .or. size (x) /= 1) stop 5
+if (x(1) /= '') stop 6
+  end associate
+contains
+  function f() result(z)
+character(:), allocatable :: z(:)
+allocate (z, source=[''])
+  end function f
+end
--
2.35.3



Re: [Patch, fortran] PR59104

2024-06-09 Thread Harald Anlauf

Hi Paul,

your approach sounds entirely reasonable.

But as the following addition to the testcase shows, there seem to
be loopholes left.

When I add the following to function f:

 integer :: l1(size(y))
 integer :: l2(size(z))
 print *, size (l1), size (l2), size (z)

I get:

   0   0   3

Expected:

   2   3   3

Can you please check?

Thanks,
Harald


Am 09.06.24 um 17:57 schrieb Paul Richard Thomas:

Hi All,

I have extended the testcase - see below and have
s/dependent_decls_2/dependent_decls_2.f90/ in the ChnageLog.

Cheers

Paul

! { dg-do run }
!
! Fix for PR59104 in which the dependence on the old style function result
! was not taken into account in the ordering of auto array allocation and
! characters with dependent lengths.
!
! Contributed by Tobias Burnus  
!
module m
implicit none
integer, parameter :: dp = kind([double precision::])
contains
   function f(x)
  integer, intent(in) :: x
  real(dp) f(x/2)
  real(dp) g(x/2)
  integer y(size (f)+1) ! This was the original problem
  integer z(size (f) + size (y)) ! Found in development of the fix
  integer w(size (f) + size (y) + x) ! Check dummy is OK
  f = 10.0
  y = 1! Stop -Wall from complaining
  z = 1
  g = 1
  w = 1
  if (size (f) .ne. 1) stop 1
  if (size (g) .ne. 1) stop 2
  if (size (y) .ne. 2) stop 3
  if (size (z) .ne. 3) stop 4
  if (size (w) .ne. 5) stop 5
   end function f
   function e(x) result(f)
  integer, intent(in) :: x
  real(dp) f(x/2)
  real(dp) g(x/2)
  integer y(size (f)+1)
  integer z(size (f) + size (y)) ! As was this.
  integer w(size (f) + size (y) + x)
  f = 10.0
  y = 1
  z = 1
  g = 1
  w = 1
  if (size (f) .ne. 2) stop 6
  if (size (g) .ne. 2) stop 7
  if (size (y) .ne. 3) stop 8
  if (size (z) .ne. 5) stop 9
  if (size (w) .ne. 9) stop 10
   end function
   function d(x)  ! After fixes to arrays, what was needed was known!
 integer, intent(in) :: x
 character(len = x/2) :: d
 character(len = len (d)) :: line
 character(len = len (d) + len (line)) :: line2
 character(len = len (d) + len (line) + x) :: line3
 line = repeat ("a", len (d))
 line2 = repeat ("b", x)
 line3 = repeat ("c", len (line3))
 if (len (line2) .ne. x) stop 11
 if (line3 .ne. "") stop 12
 d = line
   end
end module m

program p
use m
implicit none
real(dp) y

y = sum (f (2))
if (int (y) .ne. 10) stop 13
y = sum (e (4))
if (int (y) .ne. 20) stop 14
if (d (4) .ne. "aa") stop 15
end program p



On Sun, 9 Jun 2024 at 07:14, Paul Richard Thomas <
paul.richard.tho...@gmail.com> wrote:


Hi All,

The attached fixes a problem that, judging by the comments, has been
looked at periodically over the last ten years but just looked to be too
fiendishly complicated to fix. This is not in small part because of the
confusing ordering of dummies in the tlink chain and the unintuitive
placement of all deferred initializations to the front of the init chain in
the wrapped block.

The result of the existing ordering is that the initialization code for
non-dummy variables that depends on the function result occurs before any
initialization code for the function result itself. The fix ensures that:
(i) These variables are placed correctly in the tlink chain, respecting
inter-dependencies; and (ii) The dependent initializations are placed at
the end of the wrapped block init chain.  The details appear in the
comments in the patch. It is entirely possible that a less clunky fix
exists but I failed to find it.

OK for mainline?

Regards

Paul











Re: [Fortran, Patch, PR 96992, V4] Fix Class arrays of different ranks are rejected as storage association argument

2024-07-10 Thread Harald Anlauf

Hi Andre,

Am 10.07.24 um 10:45 schrieb Andre Vehreschild:

Hi Harald,

thanks for the review. I totally agree, that this patch has gotten bigger than
I expected (and wanted). But things are as they are.

About the coding style: I have worked in so many projects, that I consider a
consistent coding style luxury. I esp. do not have my own one anymore. The
formating you are seeing in my patches is the result of clang-format with the
provided parameter file in contrib/clang-format. I was happy to have a tool
to do the formatting, that I could integrate into my IDE, because previously it
was hard to mimic the GNU style. I try to get to the GNU style as good as
possible, where I consider clang-format doing garbage.

I see that clang-format has a "very specific opinion" on how to format the
lines you mentioned, but it will "correct" them any time I change them and
touch them later. I now have forbidden clang-format to touch the code lines,
but this means to add formatter specific comments. Is this ok?


yes, this is much better now!  Thanks.

(I entirely rely on Emacs' formatting when working with C.  Sometimes
the indentation at first may appear unexpected, but in most of these
cases I find that it helps to just use explicit parentheses to convince
Emacs.  This is documented.)


About the assumed size arrays, that was a small change and is added now.


Great!


Note, the runtime part of the patch (pr96992_3p1.patch) did not change and is
therefore not updated.

Regtests ok on x86_64-pc-linux-gnu/Fedora 39. Ok for mainline?


Yes, this is OK now.

Thanks for the patch and your patience ;-)

Harald



Regards,
Andre

On Fri, 5 Jul 2024 22:10:16 +0200
Harald Anlauf  wrote:


Hi Andre,

Am 03.07.24 um 12:58 schrieb Andre Vehreschild:

Hi Harald,

I am sorry for the long delay, but fixing the negative stride lead from one
issue to the next. I finally got a version that does not regress. Please
have a look.

This patch has two parts:
1. The runtime library part in pr96992_3p1.patch and
2. the compiler changes in pr96992_3p2.patch.

In my branch also the two patches from Paul for pr59104 and pr102689 are
living, which might lead to small shifts during application of the patches.

NOTE, this patch adds internal packing and unpacking of class arrays
similar to the regular pack and unpack. I think this is necessary, because
the regular un-/pack does not use the vptr's _copy routine for moving data
and therefore may produce bugs.

The un-/pack_class routines are yet only used for converting a derived type
array to a class array. Extending their use when a UN-/PACK() is applied on
a class array is still to be done (as part of another PR).

Regtests fine on x86_64-pc-linux-gnu/ Fedora 39.


this is a really huge patch to review, and I am not sure that I can do
this without help from others.  Paul?  Anybody else?

As far as I can tell for now:

- pr96992_3p1.patch (the libgfortran part) looks good to me.

- git had some whitespace issues with pr96992_3p2.patch as attached,
but I could fix that locally and do some testing parallel to reading.

A few advance comments on the latter patch:

- my understanding is that the PR at the end of a summary line should be
like in:

Fortran: Fix rejecting class arrays of different ranks as storage
association argument [PR96992]

I was told that this helps people explicitly scanning for the PR
number in that place.

- some rewrites of logical conditions change the coding style from
what it recommended GNU coding style, and I find the more compact
way used in some places harder to grok (but that may be just me).
Example:

@@ -8850,20 +8857,24 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr
* expr, bool g77,
 /* There is no need to pack and unpack the array, if it is contiguous
and not a deferred- or assumed-shape array, or if it is simply
contiguous.  */
-  no_pack = ((sym && sym->as
- && !sym->attr.pointer
- && sym->as->type != AS_DEFERRED
- && sym->as->type != AS_ASSUMED_RANK
- && sym->as->type != AS_ASSUMED_SHAPE)
- ||
-(ref && ref->u.ar.as
- && ref->u.ar.as->type != AS_DEFERRED
+  no_pack = false;
+  gfc_array_spec *as;
+  if (sym)
+{
+  symbol_attribute *attr
+   = &(IS_CLASS_ARRAY (sym) ? CLASS_DATA (sym)->attr : sym->attr);
+  as = IS_CLASS_ARRAY (sym) ? CLASS_DATA (sym)->as : sym->as;
+  no_pack
+   = (as && !attr->pointer && as->type != AS_DEFERRED
+  && as->type != AS_ASSUMED_RANK && as->type != AS_ASSUMED_SHAPE);
+}
+  if (ref && ref->u.ar.as)
+no_pack = no_pack
+ || (ref->u.ar.as->type != AS_DEFERRED
  && ref->u.ar.as-

Re: Lower zeroing array assignment to memset for allocatable arrays

2024-07-10 Thread Harald Anlauf

Hi Prathamesh,

Am 10.07.24 um 13:22 schrieb Prathamesh Kulkarni:

Hi,
The attached patch lowers zeroing array assignment to memset for allocatable 
arrays.

For example:
subroutine test(z, n)
 implicit none
 integer :: n
 real(4), allocatable :: z(:,:,:)

 allocate(z(n, 8192, 2048))
 z = 0
end subroutine

results in following call to memset instead of 3 nested loops for z = 0:
 (void) __builtin_memset ((void *) z->data, 0, (unsigned long) MAX_EXPR dim[0].ubound - 
z->dim[0].lbound, -1> + 1) * (MAX_EXPR dim[1].ubound - z->dim[1].lbound, -1> + 1)) * (MAX_EXPR 
dim[2].ubound - z->dim[2].lbound, -1> + 1)) * 4));

The patch significantly improves speedup for an internal Fortran application on 
AArch64 -mcpu=grace (and potentially on other AArch64 cores too).
Bootstrapped+tested on aarch64-linux-gnu.
Does the patch look OK to commit ?


no, it is NOT ok.

Consider:

subroutine test0 (n, z)
  implicit none
  integer :: n
  real, pointer :: z(:,:,:) ! need not be contiguous!
  z = 0
end subroutine

After your patch this also generates a memset, but this cannot be true
in general.  One would need to have a test on contiguity of the array
before memset can be used.

In principle this is a nice idea, and IIRC there exists a very
old PR on this (by Thomas König?).  So it might be worth
pursuing.

Thanks,
Harald



Signed-off-by: Prathamesh Kulkarni 

Thanks,
Prathamesh




Re: Lower zeroing array assignment to memset for allocatable arrays

2024-07-11 Thread Harald Anlauf

Hi Prathamesh!

Am 11.07.24 um 12:16 schrieb Prathamesh Kulkarni:




-Original Message-
From: Harald Anlauf 
Sent: Thursday, July 11, 2024 12:53 AM
To: Prathamesh Kulkarni ; gcc-
patc...@gcc.gnu.org; fort...@gcc.gnu.org
Subject: Re: Lower zeroing array assignment to memset for allocatable
arrays

External email: Use caution opening links or attachments


Hi Prathamesh,

Am 10.07.24 um 13:22 schrieb Prathamesh Kulkarni:

Hi,
The attached patch lowers zeroing array assignment to memset for

allocatable arrays.


For example:
subroutine test(z, n)
  implicit none
  integer :: n
  real(4), allocatable :: z(:,:,:)

  allocate(z(n, 8192, 2048))
  z = 0
end subroutine

results in following call to memset instead of 3 nested loops for z

= 0:

  (void) __builtin_memset ((void *) z->data, 0, (unsigned long)
MAX_EXPR dim[0].ubound - z->dim[0].lbound, -1> + 1) *
(MAX_EXPR dim[1].ubound - z->dim[1].lbound, -1> + 1)) *

(MAX_EXPR

dim[2].ubound - z->dim[2].lbound, -1> + 1)) * 4));

The patch significantly improves speedup for an internal Fortran

application on AArch64 -mcpu=grace (and potentially on other AArch64
cores too).

Bootstrapped+tested on aarch64-linux-gnu.
Does the patch look OK to commit ?


no, it is NOT ok.

Consider:

subroutine test0 (n, z)
implicit none
integer :: n
real, pointer :: z(:,:,:) ! need not be contiguous!
z = 0
end subroutine

After your patch this also generates a memset, but this cannot be true
in general.  One would need to have a test on contiguity of the array
before memset can be used.

In principle this is a nice idea, and IIRC there exists a very old PR
on this (by Thomas König?).  So it might be worth pursuing.

Hi Harald,
Thanks for the suggestions!
The attached patch checks gfc_is_simply_contiguous(expr, true, false) before 
lowering to memset,
which avoids generating memset for your example above.


This is much better, as it avoids generating false memsets where
it should not.  However, you now miss cases where the array is a
component reference, as in:

subroutine test_dt (dt)
  implicit none
  type t
 real, allocatable :: x(:,:,:) ! contiguous!
 real, pointer, contiguous :: y(:,:,:) ! contiguous!
 real, pointer :: z(:,:,:) ! need not be contiguous!
  end type t
  type(t) :: dt
  dt% x = 0  ! memset possible!
  dt% y = 0  ! memset possible!
  dt% z = 0  ! memset NOT possible!
end subroutine

You'll need to cycle through the component references and
apply the check for contiguity to the ultimate component,
not the top level.

Can you have another look?

Thanks,
Harald


Bootstrapped+tested on aarch64-linux-gnu.
Does the attached patch look OK ?

Signed-off-by: Prathamesh Kulkarni 

Thanks,
Prathamesh


Thanks,
Harald



Signed-off-by: Prathamesh Kulkarni 

Thanks,
Prathamesh







Re: [PATCH] fortran: Factor the evaluation of MINLOCK/MAXLOC's BACK argument

2024-07-11 Thread Harald Anlauf

Hi Mikael,

Am 11.07.24 um 21:55 schrieb Mikael Morin:

From: Mikael Morin 

Hello,

I discovered this while testing the inline MINLOC/MAXLOC (aka PR90608) patches.
Regression tested on x86_64-linux.
OK for master?


this is a nice finding!  (NAG seems to fail on the cases with
array size 0, while Intel gets it right.)

The commit message promises to cover all variations ("with/out NANs"?)
but I fail to see these.  Were these removed in the submission?

Otherwise the patch looks pretty simple and is OK for mainline.
But do not forget to s/MINLOCK/MINLOC/ in the summary.

Thanks for the patch!

Harald


-- 8< --

Move the evaluation of the BACK argument out of the loop in the inline code
generated for MINLOC or MAXLOC.  For that, add a new (scalar) element
associated with BACK to the scalarization loop chain, evaluate the argument
with the context of that element, and let the scalarizer do its job.

The problem was not only a missed optimisation, but also a wrong code
one in the cases where the expression associated with BACK is not free of
side-effects, making multiple evaluations observable.

The new tests check the evaluation count of the BACK argument, and try to
cover all the variations (with/out NANs, constant or unknown shape, absent
or scalar or array MASK) supported by the inline implementation of the
functions.  Care has been taken to not check the case of a constant .FALSE.
MASK, for which the evaluation of BACK can be elided.

gcc/fortran/ChangeLog:

* trans-intrinsic.cc (gfc_conv_intrinsic_minmaxloc): Create a new
scalar scalarization chain element if BACK is present.  Add it to
the loop.  Set the scalarization chain before evaluating the
argument.

gcc/testsuite/ChangeLog:

* gfortran.dg/maxloc_5.f90: New test.
* gfortran.dg/minloc_5.f90: New test.
---
  gcc/fortran/trans-intrinsic.cc |  10 +
  gcc/testsuite/gfortran.dg/maxloc_5.f90 | 257 +
  gcc/testsuite/gfortran.dg/minloc_5.f90 | 257 +
  3 files changed, 524 insertions(+)
  create mode 100644 gcc/testsuite/gfortran.dg/maxloc_5.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minloc_5.f90

diff --git a/gcc/fortran/trans-intrinsic.cc b/gcc/fortran/trans-intrinsic.cc
index 5ea10e84060..cadbd177452 100644
--- a/gcc/fortran/trans-intrinsic.cc
+++ b/gcc/fortran/trans-intrinsic.cc
@@ -5325,6 +5325,7 @@ gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * 
expr, enum tree_code op)
gfc_actual_arglist *actual;
gfc_ss *arrayss;
gfc_ss *maskss;
+  gfc_ss *backss;
gfc_se arrayse;
gfc_se maskse;
gfc_expr *arrayexpr;
@@ -5390,6 +5391,11 @@ gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * 
expr, enum tree_code op)
  && maskexpr->symtree->n.sym->attr.dummy
  && maskexpr->symtree->n.sym->attr.optional;
backexpr = actual->next->next->expr;
+  if (backexpr)
+backss = gfc_get_scalar_ss (gfc_ss_terminator, backexpr);
+  else
+backss = nullptr;
+
nonempty = NULL;
if (maskexpr && maskexpr->rank != 0)
  {
@@ -5449,6 +5455,9 @@ gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * 
expr, enum tree_code op)
if (maskss)
  gfc_add_ss_to_loop (&loop, maskss);

+  if (backss)
+gfc_add_ss_to_loop (&loop, backss);
+
gfc_add_ss_to_loop (&loop, arrayss);

/* Initialize the loop.  */
@@ -5535,6 +5544,7 @@ gfc_conv_intrinsic_minmaxloc (gfc_se * se, gfc_expr * 
expr, enum tree_code op)
gfc_add_block_to_block (&block, &arrayse.pre);

gfc_init_se (&backse, NULL);
+  backse.ss = backss;
gfc_conv_expr_val (&backse, backexpr);
gfc_add_block_to_block (&block, &backse.pre);

diff --git a/gcc/testsuite/gfortran.dg/maxloc_5.f90 
b/gcc/testsuite/gfortran.dg/maxloc_5.f90
new file mode 100644
index 000..5d722450c8f
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/maxloc_5.f90
@@ -0,0 +1,257 @@
+! { dg-do run }
+!
+! Check that the evaluation of MAXLOC's BACK argument is made only once
+! before the scalarisation loops.
+
+program p
+  implicit none
+  integer, parameter :: data10(*) = (/ 7, 4, 7, 6, 6, 4, 6, 3, 9, 8 /)
+  logical, parameter :: mask10(*) = (/ .false., .true., .false., &
+   .false., .true., .true.,  &
+   .true. , .true., .false., &
+   .false. /)
+  integer :: calls_count = 0
+  call check_int_const_shape
+  call check_int_const_shape_scalar_mask
+  call check_int_const_shape_array_mask
+  call check_int_const_shape_optional_mask_present
+  call check_int_const_shape_optional_mask_absent
+  call check_int_const_shape_empty
+  call check_int_alloc
+  call check_int_alloc_scalar_mask
+  call check_int_alloc_array_mask
+  call check_int_alloc_empty
+  call check_real_const_shape
+  call check_real_const_shape_scalar_mask
+  call check_real_const_shape_array_mask
+  call check_real_const_shape_optional_mask_present
+  call check_real_const_shape_optional_mask_absen

Re: Lower zeroing array assignment to memset for allocatable arrays

2024-07-12 Thread Harald Anlauf

Hi Prathamesh,

Am 12.07.24 um 15:31 schrieb Prathamesh Kulkarni:

It seems that component references are not currently handled even for static 
size arrays ?
For eg:
subroutine test_dt (dt, y)
implicit none
real :: y (10, 20, 30)
type t
   real :: x(10, 20, 30)
end type t
type(t) :: dt
y = 0
dt% x = 0
end subroutine

With trunk, it generates memset for 'y' but not for dt%x.
That happens because copyable_array_p returns false for dt%x,
because expr->ref->next is non NULL:

   /* First check it's an array.  */
   if (expr->rank < 1 || !expr->ref || expr->ref->next)
 return false;

and gfc_full_array_ref_p(expr) bails out if expr->ref->type != REF_ARRAY.


Indeed that check (as is) prevents the use of component refs.
(I just tried to modify the this part to cycle thru the refs,
but then I get regressions in the testsuite for some of the
coarray tests.  Furthermore, gfc_trans_zero_assign would
need further changes to handle even the constant shapes
from above.)


Looking thru git history, it seems both the checks were added in 18eaa2c0cd20 
to fix PR33370.
(Even after removing these checks, the previous patch bails out from 
gfc_trans_zero_assign because
GFC_DESCRIPTOR_TYPE_P (type) returns false for component ref and ends up 
returning NULL_TREE)
I am working on extending the patch to handle component refs for statically 
sized as well as allocatable arrays.

Since it looks like a bigger change and an extension to current functionality, 
will it be OK to commit the previous patch as-is (if it looks correct)
and address component refs in follow up one ?


I agree that it is reasonable to defer the handling of arrays as
components of derived types, and recommend to do the following:

- replace "&& gfc_is_simply_contiguous (expr, true, false))" in your
  last patch by "&& gfc_is_simply_contiguous (expr, false, false))",
  as that would also allow to treat

  z(:,::1,:) = 0

  as contiguous if z is allocatable or a contiguous pointer.

- open a PR in bugzilla to track the missed-optimization for
  the cases we discussed here, and link the discussion in the ML.

Your patch then will be OK for mainline.

Thanks,
Harald


Thanks,
Prathamesh


Thanks,
Harald


Bootstrapped+tested on aarch64-linux-gnu.
Does the attached patch look OK ?

Signed-off-by: Prathamesh Kulkarni 

Thanks,
Prathamesh


Thanks,
Harald



Signed-off-by: Prathamesh Kulkarni 

Thanks,
Prathamesh








Re: [Patch, fortran] PR84868 - [11/12/13/14/15 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-07-14 Thread Harald Anlauf

Hi Paul,

at first sight the patch seems to be the right approach, but
it breaks for the following two variations:

(1) LEN_TRIM is elemental, but the following is erroneously rejected:

  function g(n) result(z)
integer,  intent(in) :: n
character, parameter :: d(3,3) = 'x'
character(len_trim(d(n,n))) :: z
z = d(n,n)
  end

This is fixed here by commenting/removing the line

  expr->rank = 1;

as the result shall have the same shape as the argument.
Can you check?

(2) The handling of namespaces is problematic: using the same name
for a parameter within procedures in the same scope generates another
ICE.  The following testcase demonstrates this:

module m
  implicit none
  integer :: c
contains
  function f(n) result(z)
integer,  intent(in) :: n
character, parameter :: c(3) = ['x', 'y', 'z']
character(len_trim(c(n)))  :: z
z = c(n)
  end
  function h(n) result(z)
integer,  intent(in) :: n
character, parameter :: c(3,3) = 'x'
character(len_trim(c(n,n)))  :: z
z = c(n,n)
  end
end
program p
  use m
  implicit none
  print *, f(2)
  print *, h(1)
end

I get:

pr84868-z0.f90:22:15:

   22 |   print *, h(1)
  |   1
internal compiler error: in gfc_conv_descriptor_stride_get, at
fortran/trans-array.cc:483
0x243e156 internal_error(char const*, ...)
../../gcc-trunk/gcc/diagnostic-global-context.cc:491
0x96dd70 fancy_abort(char const*, int, char const*)
../../gcc-trunk/gcc/diagnostic.cc:1725
0x749d68 gfc_conv_descriptor_stride_get(tree_node*, tree_node*)
../../gcc-trunk/gcc/fortran/trans-array.cc:483
[rest of traceback elided]

Renaming the parameter array in h solves the problem.

Am 13.07.24 um 17:57 schrieb Paul Richard Thomas:

Hi All,

Harald has pointed out that I attached the ChangeLog twice and the patch
not at all :-(

Please find the patch duly attached.

Paul


On Sat, 13 Jul 2024 at 10:58, Paul Richard Thomas <
paul.richard.tho...@gmail.com> wrote:


Hi All,

After messing around with argument mapping, where I found and fixed
another bug, I realised that the problem lay with simplification of
len_trim with an argument that is the element of a parameter array. The fix
was then a straightforward lift of existing code in expr.cc. The mapping
bug is also fixed by supplying the se string length when building character
typespecs.

Regtests just fine. OK for mainline? I believe that this is safe for
backporting to 14-branch before the 14.2 release - thoughts?


If you manage to correct/fix the above issues, I am fine with
backporting, as this appears a very reasonable fix.

Thanks,
Harald


Regards

Paul







Re: [Patch, fortran] PR84868 - [11/12/13/14/15 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-07-15 Thread Harald Anlauf

Hi Paul, Andre,

at the risk of getting stoned to death, here's an example:

module m
  implicit none
  integer :: c
contains
  function f(n) result(z)
integer,  intent(in) :: n
character, parameter :: c(3) = ['x', 'y', 'z']
character(len_trim(c(n)))  :: z
z = c(n)
  end
  function h(n) result(z)
integer,  intent(in) :: n
character, parameter :: c(3,3) = 'x'
character(len_trim(c(n,n)))  :: z
z = c(n,n)
  contains
function k(n) result(z)
  integer,  intent(in) :: n
  character, parameter :: c(3) = ['*', '+', '-']
  character(len_trim(c(n)))  :: z
  z = c(n)
end
  end
end
program p
  use m
  implicit none
  print *, f(2)
  print *, h(1)
end

% gfc-15 pr84868-z0.f90 -fdump-fortran-original

Namespace: A-Z: (UNKNOWN 0)
procedure name = m
  symtree: '@0'  || symbol: '_len_trim_c_h' from namespace 'h'
  symtree: '@1'  || symbol: '_len_trim_c_k' from namespace 'k'
  symtree: '@2'  || symbol: '_len_trim_c_f' from namespace 'f'
  symtree: 'c'   || symbol: 'c'
[...]
f951: internal compiler error: in gfc_create_module_variable, at
fortran/trans-decl.cc:5515
0x2438776 internal_error(char const*, ...)
../../gcc-trunk/gcc/diagnostic-global-context.cc:491
0x96df24 fancy_abort(char const*, int, char const*)
../../gcc-trunk/gcc/diagnostic.cc:1725
0x752d8a gfc_create_module_variable
../../gcc-trunk/gcc/fortran/trans-decl.cc:5515
0x752d8a gfc_create_module_variable
../../gcc-trunk/gcc/fortran/trans-decl.cc:5428
[...]

So you are very close!

My example is likely very artificial, but nevertheless legal.

We hit the following assert:

  gcc_assert (sym->ns->proc_name->attr.flavor == FL_MODULE
  || (sym->ns->parent->proc_name->attr.flavor == FL_MODULE
  && sym->fn_result_spec));

For '_len_trim_c_k':

Breakpoint 1, gfc_create_module_variable (sym=0x32af2f0)
at ../../gcc-trunk/gcc/fortran/trans-decl.cc:5515
5515  gcc_assert (sym->ns->proc_name->attr.flavor == FL_MODULE
(gdb) p sym->ns->proc_name->attr.flavor
$9 = FL_PROCEDURE
(gdb) p sym->ns->parent->proc_name->attr.flavor
$10 = FL_PROCEDURE

This is not good.

Can we prevent the export of this artificial symbol?

Otherwise the patch is fine.

Thanks,
Harald


Am 15.07.24 um 12:23 schrieb Andre Vehreschild:

Hi Paul,

I tried to "break" your patch, but I failed. (I tried having same function in
both modules with identical signature; but I do not get a symbol collision). So
to me the patch looks fine now. But you may want to give Harald some time for a
look.

Thanks for the patch,
Andre

On Mon, 15 Jul 2024 10:41:45 +0100
Paul Richard Thomas  wrote:


I've done it again! Patch duly added.

Paul

On Mon, 15 Jul 2024 at 09:21, Paul Richard Thomas <
paul.richard.tho...@gmail.com> wrote:


Hi Harald,

Thank you for the review and for the testing to destruction. Both issues
are fixed in the attached patch. Note the new function 'h', which both
tests that the namespace confusion is fixed and that the elemental-ness of
LEN_TRIM is respected.

The patch continues to regtest OK. If I don't receive anymore
comments/corrections, I will commit tomorrow morning.

Regards

Paul


On Sun, 14 Jul 2024 at 19:50, Harald Anlauf  wrote:


Hi Paul,

at first sight the patch seems to be the right approach, but
it breaks for the following two variations:

(1) LEN_TRIM is elemental, but the following is erroneously rejected:

function g(n) result(z)
  integer,  intent(in) :: n
  character, parameter :: d(3,3) = 'x'
  character(len_trim(d(n,n))) :: z
  z = d(n,n)
end

This is fixed here by commenting/removing the line

expr->rank = 1;

as the result shall have the same shape as the argument.
Can you check?

(2) The handling of namespaces is problematic: using the same name
for a parameter within procedures in the same scope generates another
ICE.  The following testcase demonstrates this:

module m
implicit none
integer :: c
contains
function f(n) result(z)
  integer,  intent(in) :: n
  character, parameter :: c(3) = ['x', 'y', 'z']
  character(len_trim(c(n)))  :: z
  z = c(n)
end
function h(n) result(z)
  integer,  intent(in) :: n
  character, parameter :: c(3,3) = 'x'
  character(len_trim(c(n,n)))  :: z
  z = c(n,n)
end
end
program p
use m
implicit none
print *, f(2)
print *, h(1)
end

I get:

pr84868-z0.f90:22:15:

 22 |   print *, h(1)
|   1
internal compiler error: in gfc_conv_descriptor_stride_get, at
fortran/trans-array.cc:483
0x243e156 internal_error(char const*, ...)

Re: [Patch, fortran] PR84868 - [11/12/13/14/15 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-07-15 Thread Harald Anlauf

Replying to myself:

Am 15.07.24 um 19:35 schrieb Harald Anlauf:

For '_len_trim_c_k':

Breakpoint 1, gfc_create_module_variable (sym=0x32af2f0)
     at ../../gcc-trunk/gcc/fortran/trans-decl.cc:5515
5515  gcc_assert (sym->ns->proc_name->attr.flavor == FL_MODULE
(gdb) p sym->ns->proc_name->attr.flavor
$9 = FL_PROCEDURE
(gdb) p sym->ns->parent->proc_name->attr.flavor
$10 = FL_PROCEDURE

This is not good.

Can we prevent the export of this artificial symbol?


Like this here (to give an idea, but otherwise untested):

diff --git a/gcc/fortran/trans-decl.cc b/gcc/fortran/trans-decl.cc
index 54ab60b4935..cc6ac7f192e 100644
--- a/gcc/fortran/trans-decl.cc
+++ b/gcc/fortran/trans-decl.cc
@@ -5455,6 +5468,13 @@ gfc_create_module_variable (gfc_symbol * sym)
&& !(sym->attr.flavor == FL_PROCEDURE && sym->attr.proc_pointer))
 return;

+  /* Do not output artificially created parameters.  */
+  if (sym->attr.flavor == FL_PARAMETER
+  && sym->name[0] == '_'
+  && sym->ns->proc_name->attr.flavor == FL_PROCEDURE
+  && sym->ns->parent->proc_name->attr.flavor == FL_PROCEDURE)
+return;
+
   if ((sym->attr.in_common || sym->attr.in_equivalence) && 
sym->backend_decl)

 {
   decl = sym->backend_decl;

Maybe one might mark the symbol already at creation time and
detect this mark here, too.

Harald




Re: Lower zeroing array assignment to memset for allocatable arrays

2024-07-15 Thread Harald Anlauf

Hi Prathamesh!

Am 15.07.24 um 15:07 schrieb Prathamesh Kulkarni:

-Original Message-
From: Harald Anlauf 
I agree that it is reasonable to defer the handling of arrays as
components of derived types, and recommend to do the following:

- replace "&& gfc_is_simply_contiguous (expr, true, false))" in your
last patch by "&& gfc_is_simply_contiguous (expr, false, false))",
as that would also allow to treat

z(:,::1,:) = 0

as contiguous if z is allocatable or a contiguous pointer.

- open a PR in bugzilla to track the missed-optimization for
the cases we discussed here, and link the discussion in the ML.

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


Your patch then will be OK for mainline.

Thanks, does the attached version look OK ?
Bootstrapped+tested on aarch64-linux-gnu, x86_64-linux-gnu.


This is now OK.

Thanks for the patch!

Harald


Thanks,
Prathamesh





Re: [Patch, fortran] PR84868 - [11/12/13/14/15 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-07-15 Thread Harald Anlauf

Am 15.07.24 um 20:27 schrieb Harald Anlauf:

Replying to myself:

Am 15.07.24 um 19:35 schrieb Harald Anlauf:

For '_len_trim_c_k':

Breakpoint 1, gfc_create_module_variable (sym=0x32af2f0)
 at ../../gcc-trunk/gcc/fortran/trans-decl.cc:5515
5515  gcc_assert (sym->ns->proc_name->attr.flavor == FL_MODULE
(gdb) p sym->ns->proc_name->attr.flavor
$9 = FL_PROCEDURE
(gdb) p sym->ns->parent->proc_name->attr.flavor
$10 = FL_PROCEDURE

This is not good.

Can we prevent the export of this artificial symbol?


Like this here (to give an idea, but otherwise untested):

diff --git a/gcc/fortran/trans-decl.cc b/gcc/fortran/trans-decl.cc
index 54ab60b4935..cc6ac7f192e 100644
--- a/gcc/fortran/trans-decl.cc
+++ b/gcc/fortran/trans-decl.cc
@@ -5455,6 +5468,13 @@ gfc_create_module_variable (gfc_symbol * sym)
  && !(sym->attr.flavor == FL_PROCEDURE && sym->attr.proc_pointer))
  return;

+  /* Do not output artificially created parameters.  */
+  if (sym->attr.flavor == FL_PARAMETER
+  && sym->name[0] == '_'
+  && sym->ns->proc_name->attr.flavor == FL_PROCEDURE
+  && sym->ns->parent->proc_name->attr.flavor == FL_PROCEDURE)
+    return;
+
    if ((sym->attr.in_common || sym->attr.in_equivalence) &&
sym->backend_decl)
  {
    decl = sym->backend_decl;

Maybe one might mark the symbol already at creation time and
detect this mark here, too.


JFTR: this regtests cleanly here.

While looking over the last version of the patch again,
the following should be corrected:

@@ -4637,6 +4637,75 @@ gfc_simplify_len_trim (gfc_expr *e, gfc_expr *kind)
   if (k == -1)
 return &gfc_bad_expr;

+  if (e->expr_type == EXPR_VARIABLE
+  && e->ts.type == BT_CHARACTER
+  && e->symtree->n.sym->attr.flavor == FL_PARAMETER
+  && e->ref && e->ref->type == REF_ARRAY
+  && e->ref->u.ar.dimen_type[0] == DIMEN_ELEMENT
+  && e->symtree->n.sym->value)
+{
+  char name[2*GFC_MAX_SYMBOL_LEN + 10];
^^ this has to be 12 now

+  gfc_namespace *ns = e->symtree->n.sym->ns;
+  gfc_symtree *st;
+  gfc_expr *expr;
+  gfc_expr *p;
+  gfc_constructor *c;
+  int cnt = 0;
+
+  sprintf (name, "_len_trim_%s_%s", e->symtree->n.sym->name,
ns->proc_name->name);

Cheers,
Harald



Re: [Patch, fortran] PR84868 - [11/12/13/14/15 Regression] ICE in gfc_conv_descriptor_offset, at fortran/trans-array.c:208

2024-07-16 Thread Harald Anlauf

Hi Paul,

Am 16.07.24 um 18:35 schrieb Paul Richard Thomas:

In answer to some of your latest points:




Can we prevent the export of this artificial symbol?




The export of this symbol is needed for interface mapping. Without it, the
original bug would reappear. If such len_trim calls are made outside of
specification expressions, the symbols are not exported as you verify with
either the parse tree dump or direct inspection of the module files from
the testcases.


I was under the impression that an interface that is not visible
at the top level of the module does not need to be exported.
And a contained procedure would satisfy that, or doesn't it?

The ICE I saw is actually a pre-existing issue reported by Gerhard:

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

Cheers,
Harald



[PATCH] Fortran: character array constructor with >= 4 constant elements [PR103115]

2024-07-18 Thread Harald Anlauf
Dear all,

here's a quite obvious fix for an ICE when processing an array constructor
where the first element is of deferred length, and at least four constant
elements followed, or an iterator with at least four elements.  There
is a code path that then tries to combine these constant elements and
take the element size of the first (variable length) element in the
constructor.

(For gcc with checking=release, no ICE occured; wrong code was generated
instead.)

Obvious fix: if we see that the element size is not constant, falls back
to the case handling the constructor element-wise.

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

Thanks,
Harald

From 5b264e77b54e211c7781d2c2e5dc324846a774a1 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Thu, 18 Jul 2024 21:15:48 +0200
Subject: [PATCH] Fortran: character array constructor with >= 4 constant
 elements [PR103115]

gcc/fortran/ChangeLog:

	PR fortran/103115
	* trans-array.cc (gfc_trans_array_constructor_value): If the first
	element of an array constructor is deferred-length character and
	therefore does not have an element size known at compile time, do
	not try to collect subsequent constant elements into a constructor
	for optimization.

gcc/testsuite/ChangeLog:

	PR fortran/103115
	* gfortran.dg/string_array_constructor_4.f90: New test.
---
 gcc/fortran/trans-array.cc|  4 +-
 .../string_array_constructor_4.f90| 59 +++
 2 files changed, 62 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/string_array_constructor_4.f90

diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
index dc3de6c3b14..c93a5f1e754 100644
--- a/gcc/fortran/trans-array.cc
+++ b/gcc/fortran/trans-array.cc
@@ -2147,7 +2147,9 @@ gfc_trans_array_constructor_value (stmtblock_t * pblock,
 	  p = gfc_constructor_next (p);
 	  n++;
 	}
-	  if (n < 4)
+	  /* Constructor with few constant elements, or element size not
+	 known at compile time (e.g. deferred-length character).  */
+	  if (n < 4 || !INTEGER_CST_P (TYPE_SIZE_UNIT (type)))
 	{
 	  /* Scalar values.  */
 	  gfc_init_se (&se, NULL);
diff --git a/gcc/testsuite/gfortran.dg/string_array_constructor_4.f90 b/gcc/testsuite/gfortran.dg/string_array_constructor_4.f90
new file mode 100644
index 000..b5b81f07395
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/string_array_constructor_4.f90
@@ -0,0 +1,59 @@
+! { dg-do run }
+! PR fortran/103115 - character array constructor with >= 4 constant elements
+!
+! This used to ICE when the first element is deferred-length character
+! or could lead to wrong results.
+
+program pr103115
+  implicit none
+  integer :: i
+  character(*), parameter :: expect(*) = [ "1","2","3","4","5" ]
+  character(5):: abc = "12345"
+  character(5), parameter :: def = "12345"
+  character(:), dimension(:), allocatable :: list
+  character(:), dimension(:), allocatable :: titles
+  titles = ["1"]
+  titles = [ titles&
+,"2"&
+,"3"&
+,"4"&
+,"5"&  ! used to ICE
+]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 1
+  if (any (titles  /= expect))   stop 2
+  titles = ["1"]
+  titles = [ titles, (char(48+i),i=2,5) ]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 3
+  if (any (titles  /= expect))   stop 4
+  titles = ["1"]
+  titles = [ titles, ("2345"(i:i),i=1,4) ]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 5
+  if (any (titles  /= expect))   stop 6
+  titles = ["1"]
+  titles = [ titles, (def(i:i),i=2,5) ]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 7
+  if (any (titles  /= expect))   stop 8
+  list = [ (char(48+i),i=1,5) ]
+  titles = [ list(1), (char(48+i),i=2,5) ]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 9
+  if (any (titles  /= expect))   stop 10
+  titles = ["1"]
+  titles = [ titles, (abc(i:i),i=2,5) ]
+  if (len (titles) /= 1 .or. size (titles) /= 5) stop 11
+  if (any (titles  /= expect))   stop 12
+
+  ! with typespec:
+  list = [ (char(48+i),i=1,5) ]
+  titles = [ character(2) :: list(1), (char(48+i),i=2,5) ]
+  if (len (titles) /= 2 .or. size (titles) /= 5) stop 13
+  if (any (titles  /= expect))   stop 14
+  titles = ["1"]
+  titles = [ character(2) :: titles, (char(48+i),i=2,5) ]
+  if (len (titles) /= 2 .or. size (titles) /= 5) stop 15
+  if (any (titles  /= expect))   stop 16
+  titles = ["1"]
+  titles = [ character(2) :: titles, (def(i:i),i=2,5) ]
+  if (len (titles) /= 2 .or. size (titles) /= 5) stop 17
+  if (any (titles  /= expect))   stop 18
+  deallocate (titles, list)
+end
--
2.35.3



Re: [Patch, Fortran, 96418] Fix Test coarray_alloc_comp_4.f08 ICEs

2024-06-14 Thread Harald Anlauf

Hi Andre,

the patch looks fairly simple and obvious, so OK from my side.

***

Regarding the testsuite: since you renamed one of the testcases
gfortran.dg/coarray_alloc_comp_* and moved it to gfortran.dg/coarray/,
I checked and noticed that there are other similar runtime tests for
coarrays (while some are compile-time only tests).

Do we plan to "clean" this up and move more/all related runtime
tests to the coarray/ subdirectory?  What is the general opinion on
this?

***

Thanks for the patch!

Harald


Am 14.06.24 um 09:22 schrieb Andre Vehreschild:

Hi all,

I messed up renaming of the coarray_alloc_comp-test. This is fixed in the second
version of the patch. Sorry for the inconvenience.

Additionally I figured that this patch also fixed PR fortran/103112.

Regtests ok on x86_64 Fedora 39. Ok for mainline?

Regards,
Andre

On Tue, 11 Jun 2024 16:12:38 +0200
Andre Vehreschild  wrote:


Hi all,

attached patch has already been present in 2020, but lost my attention. It
fixes an ICE in the testsuite. The old mails description is:

attached patch fixes PR96418 where the code in the testsuite when compiled
with -fcoarray=single  lead to an ICE. The reason was that the coarray object
was derefed as an array, but it was no array. Introducing the test for the
descriptor removes the ICE.

Regtests ok on x86_64-linux/Fedora 39. Ok for mainline?

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



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




Re: [Patch, fortran] PR59104

2024-06-14 Thread Harald Anlauf

Hi Paul,

this looks good to me and is OK for mainline.  When it has survived a
week or two, backporting at least to 14-branch (ideally before 14.2
release) would be a good thing!

Regarding the following excerpt of the testcase:

+! Commented out lines give implicit type warnings with gfortran and nagfor
+!character(len = len (d)) :: line4 (len (line3))
+character(len = len (line3)) :: line4 (len (line3))
+!character(len = size(len4, 1)) :: line5

I guess the last commented line should have referred to size(line4, 1),
right?  The lexical distance of len4 and line4 can be small after
long coding...

The first commented line gives no warning here, but is simply
inconsistent with a test later on, since len (d) < len (line3).
What exactly was the issue?

***

A minor nit: while you were fixing whitespace issues in the source,
you missed an indent with spaces here:

@@ -857,12 +873,26 @@ gfc_defer_symbol_init (gfc_symbol * sym)
   /* Find the first dummy arg seen after us, or the first
non-dummy arg.
  This is a circular list, so don't go past the head.  */
   while (p != head
- && (!p->attr.dummy || p->dummy_order > sym->dummy_order))
+ && (!p->attr.dummy || decl_order (p, sym)))
 {

At least on my side there is no tab...
(It is fine in a similar code later on.)

***

Finally a big thanks for the patch!

Harald


Am 13.06.24 um 23:43 schrieb Paul Richard Thomas:

Hi Both,

Thanks for the highly constructive comments. I think that I have
incorporated them fully in the attached.

OK for mainline and ...?

Paul


On Mon, 10 Jun 2024 at 08:19, Andre Vehreschild  wrote:


Hi Paul,

while looking at your patch I see calls to gfc_add_init_cleanup (...,
back),
while the function signature is gfc_add_init_cleanup (..., bool front).
This
slightly confuses me. I would at least expect to see
gfc_add_init_cleanup(...,
!back) calls. Just to get the semantics right.

Then I wonder why not doing:

diff --git a/gcc/fortran/dependency.cc b/gcc/fortran/dependency.cc
index bafe8cbc5bc..97ace8c778e 100644
--- a/gcc/fortran/dependency.cc
+++ b/gcc/fortran/dependency.cc
@@ -2497,3 +2497,63 @@ gfc_omp_expr_prefix_same (gfc_expr *lexpr, gfc_expr
*rexpr)
return true;
  }
+
+
+/* gfc_function_dependency returns true for non-dummy symbols with
dependencies
+   on an old-fashioned function result (ie. proc_name =
proc_name->result).
+   This is used to ensure that initialization code appears after the
function
+   result is treated and that any mutual dependencies between these
symbols are
+   respected.  */
+
+static bool
+dependency_fcn (gfc_expr *e, gfc_symbol *sym,
+int *f ATTRIBUTE_UNUSED)
+{
+  return (e && e->expr_type == EXPR_VARIABLE
+  && e->symtree
+  && e->symtree->n.sym == sym);
+}

Instead of the multiple if-statements?

+
+bool
+gfc_function_dependency (gfc_symbol *sym, gfc_symbol *proc_name)
+{
+  bool front = false;
+
+  if (proc_name && proc_name->attr.function
+  && proc_name == proc_name->result
+  && !(sym->attr.dummy || sym->attr.result))
+{
+  if (sym->as && sym->as->type == AS_EXPLICIT)
+   {
+ for (int dim = 0; dim < sym->as->rank; dim++)
+   {
+ if (sym->as->lower[dim]
+ && sym->as->lower[dim]->expr_type != EXPR_CONSTANT)
+   front = gfc_traverse_expr (sym->as->lower[dim], proc_name,
+  dependency_fcn, 0);
+ if (front)
+   break;
+ if (sym->as->upper[dim]
+ && sym->as->upper[dim]->expr_type != EXPR_CONSTANT)
+   front = gfc_traverse_expr (sym->as->upper[dim], proc_name,
+  dependency_fcn, 0);
+ if (front)
+   break;
+   }
+   }
+
+  if (sym->ts.type == BT_CHARACTER
+ && sym->ts.u.cl && sym->ts.u.cl->length
+ && sym->ts.u.cl->length->expr_type != EXPR_CONSTANT)
+   front = gfc_traverse_expr (sym->ts.u.cl->length, proc_name,
+  dependency_fcn, 0);

This can overwrite a previous front == true, right? Is this intended?

+}
+  return front;
+ }

The rest - besides the front-back confusion - looks fine to me. Thanks for
the
patch.

Regards,
 Andre

On Sun, 9 Jun 2024 07:14:39 +0100
Paul Richard Thomas  wrote:


Hi All,

The attached fixes a problem that, judging by the comments, has been

looked

at periodically over the last ten years but just looked to be too
fiendishly complicated to fix. This is not in small part because of the
confusing ordering of dummies in the tlink chain and the unintuitive
placement of all deferred initializations to the front of the init chain

in

the wrapped block.

The result of the existing ordering is that the initialization code for
non-dummy variables that depends on the function result occurs before any
initialization code for the function result itself. The fix ens

Re: [Fortran, Patch, PR 96992] Fix Class arrays of different ranks are rejected as storage association argument

2024-06-16 Thread Harald Anlauf

Hi Andre,

Am 14.06.24 um 17:05 schrieb Andre Vehreschild:

Hi all,

I somehow got assigned to this PR so I fixed it. GFortran was ICEing because of
the ASSUME_RANK in a derived to class conversion. After fixing this, storage
association was producing segfaults. The "shape conversion" of the class array
as dummy argument was not initializing the dim 0 stride and with that grabbing
into the memory somewhere. This is now fixed and

regtests fine on x86_64 Fedora 39. Ok for mainline?


the patch fixes the testcase in your submission, but not the following
slight variation of the main program:

module foo_mod
  implicit none
  type foo
 integer :: i
  end type foo
contains
  subroutine d1(x,n)
integer, intent(in) :: n
integer :: i
class (foo), intent(out) :: x(n)
select type(x)
class is(foo)
   x(:)%i = (/ (42 + i, i = 1, n ) /)
class default
   stop 1
end select
  end subroutine d1
  subroutine d2(x,n)
integer, intent(in) :: n
integer :: i
class (foo), intent(in) :: x(n,n,n)
select type (x)
class is (foo)
   print *,x%i
   if ( any( x%i /= reshape((/ (42 + i, i = 1, n ** 3 ) /), [n, n, 
n] ))) stop 2

class default
   stop 3
end select
  end subroutine d2
end module foo_mod
program main
  use foo_mod
  implicit none
  type (foo), dimension(:), allocatable :: f
  integer :: n
  n = 2
  allocate (f(n*n*n))
  ! Original testcase:
  call d1(f,n*n*n)
  call d2(f,n)  ! OK
  call d1(f(1:n*n*n),n*n*n)
  print *, "After call d1(f(1:n*n*n:1),n*n*n):"
  print *, f%i
  call d2(f(1:n*n*n),n) ! OK
  ! Using stride -1:
  call d1(f(n*n*n:1:-1),n*n*n)
  print *, "After call d1(f(n*n*n:1:-1),n*n*n):"
  print *, f%i
  call d2(f(n*n*n:1:-1),n)  ! not OK
  deallocate (f)
end program main

While this runs fine with the latest Intel compiler, gfortran including
your patch prints:

  43  44  45  46  47 
48  49  50

 After call d1(f(1:n*n*n:1),n*n*n):
  43  44  45  46  47 
48  49  50
  43  44  45  46  47 
48  49  50

 After call d1(f(n*n*n:1:-1),n*n*n):
  50  49  48  47  46 
45  44  43
  43   0   0  49   0 
34244976   034238480

STOP 2

So while the negative stride (-1) in the call to d1 appears to
work as it should, it does not work properly for the call to d2.
The first array element is fine in d2, but anything else isn't.

Do you see what goes wrong here?

(This may be a more general, pre-existing issue in a different place.)

Thanks,
Harald

P.S.: regarding your commit message, I think the reference to the pr
in brackets should be moved to the end of the summary line, i.e. for

Fortran: [PR96992] Fix rejecting class arrays of different ranks as 
storage association argument.


the "[PR96992" should be moved.  Makes it also easier to read.


I assume this patch could be fixing some other PRs with class array's parameter
passing, too. If that sounds familiar, feel free to point me to them.

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





Re: [Patch, Fortran, 96418] Fix Test coarray_alloc_comp_4.f08 ICEs

2024-06-17 Thread Harald Anlauf

Hi Andre,

Am 17.06.24 um 09:51 schrieb Andre Vehreschild:

Regarding your question on the coarray-tests that are not in the
coarray-directory: These test in most cases test only one method of
implementing coarrays. I.e., they are either testing just -fcoarray=single or
-fcoarray=lib -lcaf_single, which are two different approaches. The tests in
the coarray-directory test all available methods to implement coarrays.  Pushing


ah, that explains it.  I only looked at some of the test sources,
but did not think of looking at caf.exp ...


all coarray-tests into the coarray-directory will fail a lot of them, because
the behavior of -fcoarray=single and -fcoarray=lib -lcaf_single is different in
some corner cases. That's why the coarray-tests in the main gfortran-dir are
separate.

I do understand why it may be confusing, but I don't see an easy solution. Does
this answer your question?


Indeed it does!

Thanks,
Harald



[PATCH] Fortran: fix for CHARACTER(len=*) dummies with bind(C) [PR115390]

2024-06-18 Thread Harald Anlauf
Dear all,

the attached simple patch fixes warnings for use of uninitialized
temporaries for the string length before being defined.  The cause
is obvious: type sizes were being calculated before the temporaries
were set from the descriptor for the dummy passed to the BIND(C)
procedure.  Wrong code might have been possible as well.

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

Thanks,
Harald

From 95a3cefd5e84cf0d393c2606757894389c08ebba Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 18 Jun 2024 21:57:19 +0200
Subject: [PATCH] Fortran: fix for CHARACTER(len=*) dummies with bind(C)
 [PR115390]

gcc/fortran/ChangeLog:

	PR fortran/115390
	* trans-decl.cc (gfc_conv_cfi_to_gfc): Move derivation of type sizes
	for character via gfc_trans_vla_type_sizes to after character length
	has been set.

gcc/testsuite/ChangeLog:

	PR fortran/115390
	* gfortran.dg/bind_c_char_11.f90: New test.
---
 gcc/fortran/trans-decl.cc|  4 +-
 gcc/testsuite/gfortran.dg/bind_c_char_11.f90 | 45 
 2 files changed, 47 insertions(+), 2 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/bind_c_char_11.f90

diff --git a/gcc/fortran/trans-decl.cc b/gcc/fortran/trans-decl.cc
index dca7779528b..704f24be84a 100644
--- a/gcc/fortran/trans-decl.cc
+++ b/gcc/fortran/trans-decl.cc
@@ -7063,8 +7063,8 @@ gfc_conv_cfi_to_gfc (stmtblock_t *init, stmtblock_t *finally,
   if (sym->ts.type == BT_CHARACTER
   && !INTEGER_CST_P (sym->ts.u.cl->backend_decl))
 {
-  gfc_conv_string_length (sym->ts.u.cl, NULL, init);
-  gfc_trans_vla_type_sizes (sym, init);
+  gfc_conv_string_length (sym->ts.u.cl, NULL, &block);
+  gfc_trans_vla_type_sizes (sym, &block);
 }

   /* gfc->data = cfi->base_addr - or for scalars: gfc = cfi->base_addr.
diff --git a/gcc/testsuite/gfortran.dg/bind_c_char_11.f90 b/gcc/testsuite/gfortran.dg/bind_c_char_11.f90
new file mode 100644
index 000..5ed8e82853b
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bind_c_char_11.f90
@@ -0,0 +1,45 @@
+! { dg-do compile }
+! { dg-additional-options "-Wuninitialized" }
+!
+! PR fortran/115390 - fixes for CHARACTER(len=*) dummies with bind(C)
+
+module test
+  implicit none
+contains
+  subroutine bar(s,t) bind(c)
+character(*), intent(in) :: s,t
+optional :: t
+call foo(s,t)
+  end
+  subroutine bar1(s,t) bind(c)
+character(*), intent(in) :: s(:),t(:)
+optional :: t
+call foo1(s,t)
+  end
+  subroutine bar4(s,t) bind(c)
+character(len=*,kind=4), intent(in) :: s,t
+optional:: t
+call foo4(s,t)
+  end
+  subroutine bar5(s,t) bind(c)
+character(len=*,kind=4), intent(in) :: s(:),t(:)
+optional:: t
+call foo5(s,t)
+  end
+  subroutine foo(s,t)
+character(*), intent(in) :: s,t
+optional :: t
+  end
+  subroutine foo1(s,t)
+character(*), intent(in) :: s(:),t(:)
+optional :: t
+  end
+  subroutine foo4(s,t)
+character(len=*,kind=4), intent(in) :: s,t
+optional:: t
+  end
+  subroutine foo5(s,t)
+character(len=*,kind=4), intent(in) :: s(:),t(:)
+optional:: t
+  end
+end
--
2.35.3



Re: [Fortran, Patch, PR 96992] Fix Class arrays of different ranks are rejected as storage association argument

2024-06-19 Thread Harald Anlauf

Hi Andre,

Am 19.06.24 um 09:07 schrieb Andre Vehreschild:

Hi Harald,

thank you for the investigation and useful tips. I had to figure what went
wrong here, but I now figured, that the array needs repacking when a negative
stride is used (or at least a call to that routine, which then fixes "stuff").
I have added it, freeing the memory allocated potentially by pack, and also
updated the testcase to include the negative stride.


hmmm, the pack does not always get generated:

module foo_mod
  implicit none
  type foo
 integer :: i
  end type foo
contains
  subroutine d1(x,n)
integer, intent(in) :: n
integer :: i
class (foo), intent(out) :: x(n)
select type(x)
class is(foo)
   x(:)%i = (/ (42 + i, i = 1, n ) /)
class default
   stop 1
end select
  end subroutine d1
  subroutine d2(x,n)
integer, intent(in) :: n
integer :: i
class (foo), intent(in) :: x(n,n,n)
select type (x)
class is (foo)
   print *,"d2:  ", x%i
   if ( any( x%i /= reshape((/ (42 + i, i = 1, n ** 3 ) /), [n, n, 
n] ))) stop 2

class default
   stop 3
end select
  end subroutine d2

  subroutine d3(x,n)
integer, intent(in) :: n
integer :: i
class (foo), intent(inout) :: x(n)
select type (x)
class is (foo)
   print *,"d3_1:", x%i
   x%i = -x%i   ! Simply negate elements
   print *,"d3_2:", x%i
class default
   stop 33
end select
  end subroutine d3
end module foo_mod
program main
  use foo_mod
  implicit none
  type (foo), dimension(:), allocatable :: f
  integer :: n, k, m
  n = 2
  allocate (f(n*n*n))
  ! Original testcase:
  call d1(f,n*n*n)
  print *, "d1->:", f%i
  call d2(f,n)
  ! Ensure that array f is ok:
  print *, "d2->:", f%i

  ! The following shows that no appropriate internal pack is generated:
  call d1(f,n*n*n)
  print *, "d1->:", f%i
  m = n*n*n
  k = 3
  print *, "->d3:", f(1:m:k)%i
  call d3(f(1:m:k),1+(m-1)/k)
  print *, "d3->:", f(1:m:k)%i
  print *, "full:", f%i
  deallocate (f)
end program main


After the second version of your patch this prints:

 d1->:  43  44  45  46  47 
48  49  50
 d2:43  44  45  46  47 
48  49  50
 d2->:  43  44  45  46  47 
48  49  50
 d1->:  43  44  45  46  47 
48  49  50

 ->d3:  43  46  49
 d3_1:  43  44  45
 d3_2: -43 -44 -45
 d3->: -43  46  49
 full: -43 -44 -45  46  47 
48  49  50


While the print properly handles f(1:m:k)%i, passing it as
actual argument to subroutine d3 does not do pack/unpack.

Can you have another look?

Thanks,
Harald



Regtests fine on x86_64-pc-linux-gnu/Fedora 39. Ok for mainline?

Regards,
Andre

On Sun, 16 Jun 2024 23:27:46 +0200
Harald Anlauf  wrote:

<< snipped for brevity >>>
--
Andre Vehreschild * Email: vehre ad gmx dot de





[PATCH] Fortran: fix passing of optional dummy as actual to optional argument [PR55978]

2024-06-23 Thread Harald Anlauf
Dear all,

the attached patch fixes issues exhibited by the testcase in comment#19 of 
PR55978.

First, when passing an allocatable optional dummy array to an optional dummy,
we need to prevent accessing the data component of the array when the argument
is not present, and pass a null pointer instead.  This is straightforward.

Second, the case of a missing pointer optional dummy array should have worked,
but the presence check surprisingly did not work as expected at -O0 or -Og,
but at higher optimization levels.  Interestingly, the dump-tree looked right,
but running under gdb or investigating the assembler revealed that the order
of tests in a logical AND expression was opposed to what the tree-dump looked
like.  Replacing TRUTH_AND_EXPR by TRUTH_ANDIF_EXPR and checking the optimized
dump confirmed that this does fix the issue.

Note that the tree-dump is not changed by this replacement.  Does this mean
thar AND and ANDIF currently are not differentiated at this level?

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

Would it be ok to backport this to 14-branch, too?

Thanks,
Harald

From 94e4c66d8374a12be38637620f362acf1fba5343 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Sun, 23 Jun 2024 22:36:43 +0200
Subject: [PATCH] Fortran: fix passing of optional dummy as actual to optional
 argument [PR55978]

gcc/fortran/ChangeLog:

	PR fortran/55978
	* trans-array.cc (gfc_conv_array_parameter): Do not dereference
	data component of a missing allocatable dummy array argument for
	passing as actual to optional dummy.  Harden logic of presence
	check for optional pointer dummy by using TRUTH_ANDIF_EXPR instead
	of TRUTH_AND_EXPR.

gcc/testsuite/ChangeLog:

	PR fortran/55978
	* gfortran.dg/optional_absent_12.f90: New test.
---
 gcc/fortran/trans-array.cc| 20 ++---
 .../gfortran.dg/optional_absent_12.f90| 30 +++
 2 files changed, 46 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/optional_absent_12.f90

diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
index 19d69aec9c0..26237f43bec 100644
--- a/gcc/fortran/trans-array.cc
+++ b/gcc/fortran/trans-array.cc
@@ -8703,6 +8703,10 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77,
 	&& (sym->backend_decl != parent))
 this_array_result = false;

+  /* Passing an optional dummy argument as actual to an optional dummy?  */
+  bool pass_optional;
+  pass_optional = fsym && fsym->attr.optional && sym && sym->attr.optional;
+
   /* Passing address of the array if it is not pointer or assumed-shape.  */
   if (full_array_var && g77 && !this_array_result
   && sym->ts.type != BT_DERIVED && sym->ts.type != BT_CLASS)
@@ -8740,6 +8744,14 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77,
 	  if (size)
 	array_parameter_size (&se->pre, tmp, expr, size);
 	  se->expr = gfc_conv_array_data (tmp);
+	  if (pass_optional)
+	{
+	  tree cond = gfc_conv_expr_present (sym);
+	  se->expr = build3_loc (input_location, COND_EXPR,
+ TREE_TYPE (se->expr), cond, se->expr,
+ fold_convert (TREE_TYPE (se->expr),
+		   null_pointer_node));
+	}
   return;
 }
 }
@@ -8989,8 +9001,8 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77,
 	  tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
  fold_convert (TREE_TYPE (tmp), ptr), tmp);

-	  if (fsym && fsym->attr.optional && sym && sym->attr.optional)
-	tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR,
+	  if (pass_optional)
+	tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
    logical_type_node,
    gfc_conv_expr_present (sym), tmp);

@@ -9024,8 +9036,8 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77,
   tmp = fold_build2_loc (input_location, NE_EXPR, logical_type_node,
 			 fold_convert (TREE_TYPE (tmp), ptr), tmp);

-  if (fsym && fsym->attr.optional && sym && sym->attr.optional)
-	tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR,
+  if (pass_optional)
+	tmp = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
 			   logical_type_node,
 			   gfc_conv_expr_present (sym), tmp);

diff --git a/gcc/testsuite/gfortran.dg/optional_absent_12.f90 b/gcc/testsuite/gfortran.dg/optional_absent_12.f90
new file mode 100644
index 000..1e61d91fb6d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/optional_absent_12.f90
@@ -0,0 +1,30 @@
+! { dg-do run }
+! { dg-additional-options "-fcheck=array-temps" }
+!
+! PR fortran/55978 - comment#19
+!
+! Test passing of (missing) optional dummy to optional array argument
+
+program test
+  implicit none
+  integer, pointer :: p(:) => null()
+  call one (p)
+  call one (null())
+  call one ()
+  call three ()
+contains
+  subroutin

[PATCH] Fortran: fix ALLOCATE with SOURCE of deferred character length [PR114019]

2024-06-28 Thread Harald Anlauf
Dear all,

the attached patch fixes an ICE occuring for ALLOCATE with SOURCE
(or MOLD) of deferred character length in the scalar case, which
looked obscure because the ICE disappears at -O1 and higher.

The dump tree suggests that it is a wrong decl for the temporary
source that was e.g.

character(kind=1) source.2[1:];

whereas I had expected

character(kind=1)[1:] * source.2;

and which we now get after the patch.  Or am I missing something?

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

Thanks,
Harald

From 4d12f6d0cf63ea6a2deb5398e6478dde114e76b8 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Fri, 28 Jun 2024 21:44:06 +0200
Subject: [PATCH] Fortran: fix ALLOCATE with SOURCE of deferred character
 length [PR114019]

gcc/fortran/ChangeLog:

	PR fortran/114019
	* trans-stmt.cc (gfc_trans_allocate): Fix handling of case of
	scalar character expression being used for SOURCE.

gcc/testsuite/ChangeLog:

	PR fortran/114019
	* gfortran.dg/allocate_with_source_33.f90: New test.
---
 gcc/fortran/trans-stmt.cc |  5 +-
 .../gfortran.dg/allocate_with_source_33.f90   | 53 +++
 2 files changed, 57 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/allocate_with_source_33.f90

diff --git a/gcc/fortran/trans-stmt.cc b/gcc/fortran/trans-stmt.cc
index 93b633e212e..60275e18867 100644
--- a/gcc/fortran/trans-stmt.cc
+++ b/gcc/fortran/trans-stmt.cc
@@ -6464,7 +6464,10 @@ gfc_trans_allocate (gfc_code * code, gfc_omp_namelist *omp_allocate)
   else if (se.expr != NULL_TREE && temp_var_needed)
 	{
 	  tree var, desc;
-	  tmp = GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (se.expr)) || is_coarray ?
+	  tmp = (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (se.expr))
+		 || is_coarray
+		 || (code->expr3->ts.type == BT_CHARACTER
+		 && code->expr3->rank == 0)) ?
 		se.expr
 	  : build_fold_indirect_ref_loc (input_location, se.expr);

diff --git a/gcc/testsuite/gfortran.dg/allocate_with_source_33.f90 b/gcc/testsuite/gfortran.dg/allocate_with_source_33.f90
new file mode 100644
index 000..7b1a26c464c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/allocate_with_source_33.f90
@@ -0,0 +1,53 @@
+! { dg-do compile }
+! { dg-options "-O0" }
+!
+! PR fortran/114019 - allocation with source of deferred character length
+
+subroutine s
+  implicit none
+  character(1)  :: w   = "4"
+  character(*), parameter   :: str = "123"
+  character(5), pointer :: chr_pointer1
+  character(:), pointer :: chr_pointer2
+  character(:), pointer :: chr_ptr_arr(:)
+  character(5), allocatable :: chr_alloc1
+  character(:), allocatable :: chr_alloc2
+  character(:), allocatable :: chr_all_arr(:)
+  allocate (chr_pointer1, source=w// str//w)
+  allocate (chr_pointer2, source=w// str//w)
+  allocate (chr_ptr_arr,  source=w//[str//w])
+  allocate (chr_alloc1,   source=w// str//w)
+  allocate (chr_alloc2,   source=w// str//w)
+  allocate (chr_all_arr,  source=w//[str//w])
+  allocate (chr_pointer1, mold  =w// str//w)
+  allocate (chr_pointer2, mold  =w// str//w)
+  allocate (chr_ptr_arr,  mold  =w//[str//w])
+  allocate (chr_alloc1,   mold  =w// str//w)
+  allocate (chr_alloc2,   mold  =w// str//w)
+  allocate (chr_all_arr,  mold  =w//[str//w])
+end
+
+subroutine s2
+  implicit none
+  integer, parameter :: ck=4
+  character(kind=ck,len=1)  :: w   = ck_"4"
+  character(kind=ck,len=*), parameter   :: str = ck_"123"
+  character(kind=ck,len=5), pointer :: chr_pointer1
+  character(kind=ck,len=:), pointer :: chr_pointer2
+  character(kind=ck,len=:), pointer :: chr_ptr_arr(:)
+  character(kind=ck,len=5), allocatable :: chr_alloc1
+  character(kind=ck,len=:), allocatable :: chr_alloc2
+  character(kind=ck,len=:), allocatable :: chr_all_arr(:)
+  allocate (chr_pointer1, source=w// str//w)
+  allocate (chr_pointer2, source=w// str//w)
+  allocate (chr_ptr_arr,  source=w//[str//w])
+  allocate (chr_alloc1,   source=w// str//w)
+  allocate (chr_alloc2,   source=w// str//w)
+  allocate (chr_all_arr,  source=w//[str//w])
+  allocate (chr_pointer1, mold  =w// str//w)
+  allocate (chr_pointer2, mold  =w// str//w)
+  allocate (chr_ptr_arr,  mold  =w//[str//w])
+  allocate (chr_alloc1,   mold  =w// str//w)
+  allocate (chr_alloc2,   mold  =w// str//w)
+  allocate (chr_all_arr,  mold  =w//[str//w])
+end
--
2.35.3



[PATCH] Fortran: fix associate with assumed-length character array [PR115700]

2024-07-02 Thread Harald Anlauf
Dear all,

the attached patch addresses an effectively bogus warning about
uninitialized temporary string lengths of associate selectors.
The primary reason is that the array descriptor for a character
array is created before the corresponding string length is set.
Moving the setting of the string length temporary to the beginning
of the block solves the issue.

The patch does not solve the case for the target containing
substring references.  This needs to be addressed separately.
(So far I could not find a solution that does not regress.)

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

As the PR is marked as a regression, is it also OK for backporting?

Thanks,
Harald

From 930a1be8c623cf03f9b2e6dbddb45d0b69e152dd Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 2 Jul 2024 21:26:05 +0200
Subject: [PATCH] Fortran: fix associate with assumed-length character array
 [PR115700]

gcc/fortran/ChangeLog:

	PR fortran/115700
	* trans-stmt.cc (trans_associate_var): When the associate target
	is an array-valued character variable, the length is known at entry
	of the associate block.  Move setting of string length of the
	selector to the initialization part of the block.

gcc/testsuite/ChangeLog:

	PR fortran/115700
	* gfortran.dg/associate_69.f90: New test.
---
 gcc/fortran/trans-stmt.cc  | 18 +---
 gcc/testsuite/gfortran.dg/associate_69.f90 | 33 ++
 2 files changed, 47 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/associate_69.f90

diff --git a/gcc/fortran/trans-stmt.cc b/gcc/fortran/trans-stmt.cc
index 60275e18867..703a705e7ca 100644
--- a/gcc/fortran/trans-stmt.cc
+++ b/gcc/fortran/trans-stmt.cc
@@ -1911,6 +1911,8 @@ trans_associate_var (gfc_symbol *sym, gfc_wrapped_block *block)
   gfc_se se;
   tree desc;
   bool cst_array_ctor;
+  stmtblock_t init;
+  gfc_init_block (&init);

   desc = sym->backend_decl;
   cst_array_ctor = e->expr_type == EXPR_ARRAY
@@ -1935,10 +1937,17 @@ trans_associate_var (gfc_symbol *sym, gfc_wrapped_block *block)
 	  && !sym->attr.select_type_temporary
 	  && sym->ts.u.cl->backend_decl
 	  && VAR_P (sym->ts.u.cl->backend_decl)
+	  && se.string_length
 	  && se.string_length != sym->ts.u.cl->backend_decl)
-	gfc_add_modify (&se.pre, sym->ts.u.cl->backend_decl,
-			  fold_convert (TREE_TYPE (sym->ts.u.cl->backend_decl),
-	se.string_length));
+	{
+	  /* When the target is a variable, its length is already known.  */
+	  tree len = fold_convert (TREE_TYPE (sym->ts.u.cl->backend_decl),
+   se.string_length);
+	  if (e->expr_type == EXPR_VARIABLE)
+	gfc_add_modify (&init, sym->ts.u.cl->backend_decl, len);
+	  else
+	gfc_add_modify (&se.pre, sym->ts.u.cl->backend_decl, len);
+	}

   /* If we didn't already do the pointer assignment, set associate-name
 	 descriptor to the one generated for the temporary.  */
@@ -1978,7 +1987,8 @@ trans_associate_var (gfc_symbol *sym, gfc_wrapped_block *block)
 	}

   /* Done, register stuff as init / cleanup code.  */
-  gfc_add_init_cleanup (block, gfc_finish_block (&se.pre),
+  gfc_add_block_to_block (&init, &se.pre);
+  gfc_add_init_cleanup (block, gfc_finish_block (&init),
 			gfc_finish_block (&se.post));
 }

diff --git a/gcc/testsuite/gfortran.dg/associate_69.f90 b/gcc/testsuite/gfortran.dg/associate_69.f90
new file mode 100644
index 000..28f488bb274
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/associate_69.f90
@@ -0,0 +1,33 @@
+! { dg-do compile }
+! { dg-options "-Og -Wuninitialized -Wmaybe-uninitialized -fdump-tree-optimized" }
+!
+! PR fortran/115700 - Bogus warning for associate with assumed-length character array
+!
+subroutine mvce(x)
+  implicit none
+  character(len=*), dimension(:), intent(in)  :: x
+
+  associate (tmp1 => x)
+if (len (tmp1) /= len (x)) stop 1
+  end associate
+
+  associate (tmp2 => x(1:))
+if (len (tmp2) /= len (x)) stop 2
+  end associate
+
+  associate (tmp3 => x(1:)(:))
+if (len (tmp3) /= len (x)) stop 3
+  end associate
+
+! The following associate blocks still produce bogus warnings:
+
+! associate (tmp4 => x(:)(1:))
+!   if (len (tmp4) /= len (x)) stop 4
+! end associate
+!
+! associate (tmp5 => x(1:)(1:))
+!   if (len (tmp5) /= len (x)) stop 5
+! end associate
+end
+
+! { dg-final { scan-tree-dump-not " \\.tmp" "optimized" } }
--
2.35.3



Re: [Fortran, Patch, PR 96992, V3] Fix Class arrays of different ranks are rejected as storage association argument

2024-07-05 Thread Harald Anlauf

Hi Andre,

Am 03.07.24 um 12:58 schrieb Andre Vehreschild:

Hi Harald,

I am sorry for the long delay, but fixing the negative stride lead from one
issue to the next. I finally got a version that does not regress. Please have a
look.

This patch has two parts:
1. The runtime library part in pr96992_3p1.patch and
2. the compiler changes in pr96992_3p2.patch.

In my branch also the two patches from Paul for pr59104 and pr102689 are
living, which might lead to small shifts during application of the patches.

NOTE, this patch adds internal packing and unpacking of class arrays similar to
the regular pack and unpack. I think this is necessary, because the regular
un-/pack does not use the vptr's _copy routine for moving data and therefore
may produce bugs.

The un-/pack_class routines are yet only used for converting a derived type
array to a class array. Extending their use when a UN-/PACK() is applied on a
class array is still to be done (as part of another PR).

Regtests fine on x86_64-pc-linux-gnu/ Fedora 39.


this is a really huge patch to review, and I am not sure that I can do
this without help from others.  Paul?  Anybody else?

As far as I can tell for now:

- pr96992_3p1.patch (the libgfortran part) looks good to me.

- git had some whitespace issues with pr96992_3p2.patch as attached,
  but I could fix that locally and do some testing parallel to reading.

A few advance comments on the latter patch:

- my understanding is that the PR at the end of a summary line should be
  like in:

Fortran: Fix rejecting class arrays of different ranks as storage
association argument [PR96992]

  I was told that this helps people explicitly scanning for the PR
  number in that place.

- some rewrites of logical conditions change the coding style from
  what it recommended GNU coding style, and I find the more compact
  way used in some places harder to grok (but that may be just me).
  Example:

@@ -8850,20 +8857,24 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr
* expr, bool g77,
   /* There is no need to pack and unpack the array, if it is contiguous
  and not a deferred- or assumed-shape array, or if it is simply
  contiguous.  */
-  no_pack = ((sym && sym->as
- && !sym->attr.pointer
- && sym->as->type != AS_DEFERRED
- && sym->as->type != AS_ASSUMED_RANK
- && sym->as->type != AS_ASSUMED_SHAPE)
- ||
-(ref && ref->u.ar.as
- && ref->u.ar.as->type != AS_DEFERRED
+  no_pack = false;
+  gfc_array_spec *as;
+  if (sym)
+{
+  symbol_attribute *attr
+   = &(IS_CLASS_ARRAY (sym) ? CLASS_DATA (sym)->attr : sym->attr);
+  as = IS_CLASS_ARRAY (sym) ? CLASS_DATA (sym)->as : sym->as;
+  no_pack
+   = (as && !attr->pointer && as->type != AS_DEFERRED
+  && as->type != AS_ASSUMED_RANK && as->type != AS_ASSUMED_SHAPE);
+}
+  if (ref && ref->u.ar.as)
+no_pack = no_pack
+ || (ref->u.ar.as->type != AS_DEFERRED
  && ref->u.ar.as->type != AS_ASSUMED_RANK
- && ref->u.ar.as->type != AS_ASSUMED_SHAPE)
- ||
-gfc_is_simply_contiguous (expr, false, true));
-
-  no_pack = contiguous && no_pack;
+ && ref->u.ar.as->type != AS_ASSUMED_SHAPE);
+  no_pack
+= contiguous && (no_pack || gfc_is_simply_contiguous (expr, false,
true));

   /* If we have an EXPR_OP or a function returning an explicit-shaped
  or allocatable array, an array temporary will be generated which


I understand that this may be your personal coding style, but you
might keep in mind that reviewers have to understand the code, too...

I have not fully understood your logic when packing is now invoked.
We not only need to do it for explicit-size arrays, but also for
assumed-size.  This still fails for my slightly extended testcase
(see attached) where I pass the class array via:

  subroutine d4(x,n)
integer, intent(in) :: n
!   class (foo), intent(inout) :: x(n)  ! OK
class (foo), intent(inout) :: x(*)  ! not OK
call d3(x,n)! Simply pass assumed-size array
  end subroutine d4

I am unable to point to the places in your patch where you need to
handle that in addition.

Otherwise I was unable to see any obvious, major problem with the
patch, but then I am not fluent enough in class handling in the
gfortran FE.  So if e.g. Paul jumps in here within the next 72 hours,
it would be great.

So here comes the issue with the attached code variant.
After your patch, this prints as last 4 relevant lines:

 full: -43  44  45 -46  47
48 -49  50
 d3_1: -43  44  45
 d3_2:  43 -44 -45
 full:  43 -44 -45 -46  47
48 -49  50

while when switching the declaration of the dummy argument of d4:

 full: -43  44  45 

[PATCH] Fortran: copy-out for possibly missing OPTIONAL CLASS arguments [PR112772]

2023-11-30 Thread Harald Anlauf
Dear all,

the attached rather obvious patch fixes the first testcase of pr112772:
we unconditionally generated copy-out code for optional class arguments,
while the copy-in properly checked the presence of arguments.

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

(The second testcase is a different issue.)

Thanks,
Harald

From 38433016def0337a72cb0ef0029cd2c05d702282 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Thu, 30 Nov 2023 21:53:21 +0100
Subject: [PATCH] Fortran: copy-out for possibly missing OPTIONAL CLASS
 arguments [PR112772]

gcc/fortran/ChangeLog:

	PR fortran/112772
	* trans-expr.cc (gfc_conv_class_to_class): Make copy-out conditional
	on the presence of an OPTIONAL CLASS argument passed to an OPTIONAL
	CLASS dummy.

gcc/testsuite/ChangeLog:

	PR fortran/112772
	* gfortran.dg/missing_optional_dummy_7.f90: New test.
---
 gcc/fortran/trans-expr.cc |  9 +++
 .../gfortran.dg/missing_optional_dummy_7.f90  | 64 +++
 2 files changed, 73 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/missing_optional_dummy_7.f90

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index bfe9996ced6..6a47af39c57 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -1365,6 +1365,15 @@ gfc_conv_class_to_class (gfc_se *parmse, gfc_expr *e, gfc_typespec class_ts,
   tmp = build3_loc (input_location, COND_EXPR, void_type_node,
 			cond, tmp, tmp2);
   gfc_add_expr_to_block (&parmse->pre, tmp);
+
+  if (!elemental && full_array && copyback)
+	{
+	  tmp2 = build_empty_stmt (input_location);
+	  tmp = gfc_finish_block (&parmse->post);
+	  tmp = build3_loc (input_location, COND_EXPR, void_type_node,
+			cond, tmp, tmp2);
+	  gfc_add_expr_to_block (&parmse->post, tmp);
+	}
 }
   else
 gfc_add_block_to_block (&parmse->pre, &block);
diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_7.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_7.f90
new file mode 100644
index 000..ad9ecd8f2b6
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_7.f90
@@ -0,0 +1,64 @@
+! { dg-do run }
+! PR fortran/112772 - test absent OPTIONAL, ALLOCATABLE/POINTER class dummies
+
+program main
+  implicit none
+  type t
+  end type t
+  call test_c_a ()
+  call test_u_a ()
+  call test_c_p ()
+  call test_u_p ()
+contains
+  ! class, allocatable
+  subroutine test_c_a (msg1)
+class(t), optional, allocatable :: msg1(:)
+if (present (msg1)) stop 1
+call assert_c_a ()
+call assert_c_a (msg1)
+  end
+
+  subroutine assert_c_a (msg2)
+class(t), optional, allocatable :: msg2(:)
+if (present (msg2)) stop 2
+  end
+
+  ! unlimited polymorphic, allocatable
+  subroutine test_u_a (msg1)
+class(*), optional, allocatable :: msg1(:)
+if (present (msg1)) stop 3
+call assert_u_a ()
+call assert_u_a (msg1)
+  end
+
+  subroutine assert_u_a (msg2)
+class(*), optional, allocatable :: msg2(:)
+if (present (msg2)) stop 4
+  end
+
+  ! class, pointer
+  subroutine test_c_p (msg1)
+class(t), optional, pointer :: msg1(:)
+if (present (msg1)) stop 5
+call assert_c_p ()
+call assert_c_p (msg1)
+  end
+
+  subroutine assert_c_p (msg2)
+class(t), optional, pointer :: msg2(:)
+if (present (msg2)) stop 6
+  end
+
+  ! unlimited polymorphic, pointer
+  subroutine test_u_p (msg1)
+class(*), optional, pointer :: msg1(:)
+if (present (msg1)) stop 7
+call assert_u_p ()
+call assert_u_p (msg1)
+  end
+
+  subroutine assert_u_p (msg2)
+class(*), optional, pointer :: msg2(:)
+if (present (msg2)) stop 8
+  end
+end
--
2.35.3



Re: [PATCH] Fortran: copy-out for possibly missing OPTIONAL CLASS arguments [PR112772]

2023-12-01 Thread Harald Anlauf

Hi Mikael,

On 12/1/23 21:24, Mikael Morin wrote:

Hello,

Le 30/11/2023 à 22:06, Harald Anlauf a écrit :

the attached rather obvious patch fixes the first testcase of pr112772:
we unconditionally generated copy-out code for optional class arguments,
while the copy-in properly checked the presence of arguments.

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


Looks good.
Thanks.


ok, will commit.


(The second testcase is a different issue.)


Maybe use a separate PR?

Mikael



I just found a fix that is regtesting, and which will allow to
re-enable the test failing with ASAN in the patch for PR100651.
Will merge that fix into the previous patch and submit a v3 later.

Thanks,
Harald



[PATCH, v3] Fortran: deferred-length character optional dummy arguments [PR93762,PR100651]

2023-12-01 Thread Harald Anlauf

Dear all,

this patch extends the previous version by adding further code testing
the presence of an optional deferred-length character argument also
in the function initialization code.  This allows to re-enable a
commented-out test in v2.

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

Thanks,
Harald


On 11/28/23 20:56, Harald Anlauf wrote:

Hi FX,

On 11/28/23 18:07, FX Coudert wrote:

Hi Harald,

The patch looks OK to me. Probably wait a bit for another opinion,
since I’m not that active and I may have missed something.

Thanks,
FX


thanks for having a look.

In the meantime I got an automated mail from the Linaro testers.
According to it there is a runtime failure of the testcase on
aarch64.  I couldn't see any useful traceback or else.

I tried the testcase on x86 with different options and found
an unexpected result only with -fsanitize=undefined and only
for the case of a rank-1 dummy when there is no actual argument
and the passed to another subroutine.  (valgrind is happy.)

Reduced reproducer:

! this fails with -fsanitize=undefined
program main
   call test_rank1 ()
contains
   subroutine test_rank1 (msg1)
     character(:), optional, allocatable :: msg1(:)
     if (present (msg1)) stop 77
     call assert_rank1 ()    ! <- no problem here
     call assert_rank1 (msg1)    ! <- problematic code path
   end

   subroutine assert_rank1 (msg2)
     character(:), optional, allocatable :: msg2(:)
     if (present (msg2)) stop 99 ! <- no problem if commented
   end
end


As far as I can tell, this could be a pre-existing (latent)
issue.  By looking at the tree-dump, the only thing that
appears fishy has been there before.  But then I am only
guessing that this is the problem observed on aarch64.

I have disabled the related call in the testcase of the
attached revised version.  As I do not see anything else,
I wonder if one could proceed with the current version
but open a PR for the reduced case above, unless someone
can pinpoint the place that is responsible for the above
failure.  (Is it the caller, or rather the function entry
code in the callee?)

Cheers,
Harald

From b0a169bd70c9cd175c25b4a9543b24058596bf5e Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Fri, 1 Dec 2023 22:44:30 +0100
Subject: [PATCH] Fortran: deferred-length character optional dummy arguments
 [PR93762,PR100651]

gcc/fortran/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* trans-array.cc (gfc_trans_deferred_array): Add presence check
	for optional deferred-length character dummy arguments.
	* trans-expr.cc (gfc_conv_missing_dummy): The character length for
	deferred-length dummy arguments is passed by reference, so that
	its value can be returned.  Adjust handling for optional dummies.

gcc/testsuite/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* gfortran.dg/optional_deferred_char_1.f90: New test.
---
 gcc/fortran/trans-array.cc|   9 ++
 gcc/fortran/trans-expr.cc |  22 +++-
 .../gfortran.dg/optional_deferred_char_1.f90  | 100 ++
 3 files changed, 127 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90

diff --git a/gcc/fortran/trans-array.cc b/gcc/fortran/trans-array.cc
index bbb81f40aa9..82f60a656f3 100644
--- a/gcc/fortran/trans-array.cc
+++ b/gcc/fortran/trans-array.cc
@@ -11430,6 +11430,15 @@ gfc_trans_deferred_array (gfc_symbol * sym, gfc_wrapped_block * block)
 {
   gfc_conv_string_length (sym->ts.u.cl, NULL, &init);
   gfc_trans_vla_type_sizes (sym, &init);
+
+  /* Presence check of optional deferred-length character dummy.  */
+  if (sym->ts.deferred && sym->attr.dummy && sym->attr.optional)
+	{
+	  tmp = gfc_finish_block (&init);
+	  tmp = build3_v (COND_EXPR, gfc_conv_expr_present (sym),
+			  tmp, build_empty_stmt (input_location));
+	  gfc_add_expr_to_block (&init, tmp);
+	}
 }
 
   /* Dummy, use associated and result variables don't need anything special.  */
diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 6a47af39c57..ea087294249 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -2125,10 +2125,24 @@ gfc_conv_missing_dummy (gfc_se * se, gfc_expr * arg, gfc_typespec ts, int kind)
 
   if (ts.type == BT_CHARACTER)
 {
-  tmp = build_int_cst (gfc_charlen_type_node, 0);
-  tmp = fold_build3_loc (input_location, COND_EXPR, gfc_charlen_type_node,
-			 present, se->string_length, tmp);
-  tmp = gfc_evaluate_now (tmp, &se->pre);
+  /* Handle deferred-length dummies that pass the character length by
+	 reference so that the value can be returned.  */
+  if (ts.deferred && INDIRECT_REF_P (se->string_length))
+	{
+	  tmp = gfc_build_addr_expr (NULL_TREE, se->string_length);
+	  tmp = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp),
+ present, tmp, null_pointer_node);
+	  tmp = gfc_e

[PATCH] Fortran: allow RESTRICT qualifier also for optional arguments [PR100988]

2023-12-04 Thread Harald Anlauf
Dear all,

the attached patch picks up an observation by Tobias that we did
not specify the RESTRICT qualifier for optional arguments even
if that was allowed.  In principle this might have prevented
better optimization.

While looking more closely, I found and fixed an issue with CLASS
dummy arguments that mishandled this.  This revealed a few cases
in the testsuite that were matching the wrong patterns...

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

Thanks,
Harald

From aa25d35cb866f7f333b656938224866a70b93a69 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Mon, 4 Dec 2023 22:44:53 +0100
Subject: [PATCH] Fortran: allow RESTRICT qualifier also for optional arguments
 [PR100988]

gcc/fortran/ChangeLog:

	PR fortran/100988
	* gfortran.h (IS_PROC_POINTER): New macro.
	* trans-types.cc (gfc_sym_type): Use macro in determination if the
	restrict qualifier can be used for a dummy variable.  Fix logic to
	allow the restrict qualifier also for optional arguments, and to
	not apply it to pointer or proc_pointer arguments.

gcc/testsuite/ChangeLog:

	PR fortran/100988
	* gfortran.dg/coarray_poly_6.f90: Adjust pattern.
	* gfortran.dg/coarray_poly_7.f90: Likewise.
	* gfortran.dg/coarray_poly_8.f90: Likewise.
	* gfortran.dg/missing_optional_dummy_6a.f90: Likewise.
	* gfortran.dg/pr100988.f90: New test.

Co-authored-by: Tobias Burnus  
---
 gcc/fortran/gfortran.h|  3 +
 gcc/fortran/trans-types.cc| 13 ++--
 gcc/testsuite/gfortran.dg/coarray_poly_6.f90  |  2 +-
 gcc/testsuite/gfortran.dg/coarray_poly_7.f90  |  2 +-
 gcc/testsuite/gfortran.dg/coarray_poly_8.f90  |  2 +-
 .../gfortran.dg/missing_optional_dummy_6a.f90 |  2 +-
 gcc/testsuite/gfortran.dg/pr100988.f90| 61 +++
 7 files changed, 74 insertions(+), 11 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/pr100988.f90

diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index aa3f6cb70b4..a77441f38e7 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -4008,6 +4008,9 @@ bool gfc_may_be_finalized (gfc_typespec);
 #define IS_POINTER(sym) \
 	(sym->ts.type == BT_CLASS && sym->attr.class_ok && CLASS_DATA (sym) \
 	 ? CLASS_DATA (sym)->attr.class_pointer : sym->attr.pointer)
+#define IS_PROC_POINTER(sym) \
+	(sym->ts.type == BT_CLASS && sym->attr.class_ok && CLASS_DATA (sym) \
+	 ? CLASS_DATA (sym)->attr.proc_pointer : sym->attr.proc_pointer)

 /* frontend-passes.cc */

diff --git a/gcc/fortran/trans-types.cc b/gcc/fortran/trans-types.cc
index 084b8c3ae2c..5b11ffc3cc9 100644
--- a/gcc/fortran/trans-types.cc
+++ b/gcc/fortran/trans-types.cc
@@ -2327,8 +2327,8 @@ gfc_sym_type (gfc_symbol * sym, bool is_bind_c)
   else
 byref = 0;

-  restricted = !sym->attr.target && !sym->attr.pointer
-   && !sym->attr.proc_pointer && !sym->attr.cray_pointee;
+  restricted = (!sym->attr.target && !IS_POINTER (sym)
+		&& !IS_PROC_POINTER (sym) && !sym->attr.cray_pointee);
   if (!restricted)
 type = gfc_nonrestricted_type (type);

@@ -2384,11 +2384,10 @@ gfc_sym_type (gfc_symbol * sym, bool is_bind_c)
 	  || (sym->ns->proc_name && sym->ns->proc_name->attr.entry_master))
 	type = build_pointer_type (type);
   else
-	{
-	  type = build_reference_type (type);
-	  if (restricted)
-	type = build_qualified_type (type, TYPE_QUAL_RESTRICT);
-	}
+	type = build_reference_type (type);
+
+  if (restricted)
+	type = build_qualified_type (type, TYPE_QUAL_RESTRICT);
 }

   return (type);
diff --git a/gcc/testsuite/gfortran.dg/coarray_poly_6.f90 b/gcc/testsuite/gfortran.dg/coarray_poly_6.f90
index 53b80e442d3..344e12b4eff 100644
--- a/gcc/testsuite/gfortran.dg/coarray_poly_6.f90
+++ b/gcc/testsuite/gfortran.dg/coarray_poly_6.f90
@@ -16,6 +16,6 @@ contains
   end subroutine foo
 end
 ! { dg-final { scan-tree-dump-times "foo \\(struct __class_MAIN___T_0_1t & restrict x, void \\* restrict caf_token.., integer\\(kind=\[48\]\\) caf_offset..\\)" 1 "original" } }
-! { dg-final { scan-tree-dump-times "bar \\(struct __class_MAIN___T_0_1t \\* x, void \\* restrict caf_token.., integer\\(kind=\[48\]\\) caf_offset..\\)" 1 "original" } }
+! { dg-final { scan-tree-dump-times "bar \\(struct __class_MAIN___T_0_1t \\* restrict x, void \\* restrict caf_token.., integer\\(kind=\[48\]\\) caf_offset..\\)" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "bar \\(0B, 0B, 0\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "foo \\(&class.., y._data.token, \\(integer\\(kind=\[48\]\\)\\) class..._data.data - \\(integer\\(kind=\[48\]\\)\\) y._data.data\\);" 1 "original" } }
diff --git a/gcc/testsuite/gfortran.dg/coarray_poly_7.f90 b/gcc/testsuite/gfortran.dg/coarray_poly_7.f90
index 44f98e16e09..d8d83aea39b 100644
--- a/gc

Re: {Patch, fortran] PR112834 - Class array function selector causes chain of syntax and other spurious errors

2023-12-06 Thread Harald Anlauf

Hi Paul,

On 12/6/23 17:09, Paul Richard Thomas wrote:

Dear All,

This patch was rescued from my ill-fated and long winded attempt to provide
a fix-up for function selector references, where the function is parsed
after the procedure containing the associate/select type construct (PRs
89645 and 99065). The fix-ups broke down completely once these constructs
were enclosed by another associate construct, where the selector is a
derived type or class function. My inclination now is to introduce two pass
parsing for contained procedures.

Returning to PR112834, the patch is simple enough and is well described by
the change logs. PR111853 was fixed as a side effect of the bigger patch.
Steve Kargl had also posted the same fix on the PR.


the patch looks good, but could you please check the coding style?

@@ -6550,7 +6551,19 @@ select_type_set_tmp (gfc_typespec *ts)
   sym = tmp->n.sym;
   gfc_add_type (sym, ts, NULL);

-  if (selector->ts.type == BT_CLASS && selector->attr.class_ok
+  /* If the SELECT TYPE selector is a function we might be able to
obtain
+a typespec from the result. Since the function might not have been
+parsed yet we have to check that there is indeed a result symbol.  */
+  if (selector->ts.type == BT_UNKNOWN
+ && gfc_state_stack->construct
+ && (expr2 = gfc_state_stack->construct->expr2)
+ && expr2->expr_type == EXPR_FUNCTION
+ && expr2->symtree
+ && expr2->symtree->n.sym && expr2->symtree->n.sym->result)

Adding a line break before the second '&&' makes it more readable.

+   selector->ts = expr2->symtree->n.sym->result->ts;

@@ -2037,7 +2038,12 @@ trans_associate_var (gfc_symbol *sym,
gfc_wrapped_block *block)

   /* Class associate-names come this way because they are
 unconditionally associate pointers and the symbol is scalar.  */
-  if (sym->ts.type == BT_CLASS && CLASS_DATA (sym)->attr.dimension)
+  if (sym->ts.type == BT_CLASS && e->expr_type ==EXPR_FUNCTION)

There should be whitespace before AND after '=='.

+   {
+ gfc_conv_expr (&se, e);
+ se.expr = gfc_evaluate_now (se.expr, &se.pre);
+   }
+  else if (sym->ts.type == BT_CLASS && CLASS_DATA
(sym)->attr.dimension)


Regression tests - OK for trunk and 13-branch?

Paul



Thanks for the patch!

Harald



[PATCH] Fortran: function returning contiguous class array [PR105543]

2023-12-06 Thread Harald Anlauf
Dear all,

the attached patch fixes a rejects-valid for functions returning
a contiguous CLASS result.  The problem occurs because attr.class_ok
is inconsistent between sym and sym->result at the time the check
of the contiguous attribute is done.

I first thought that resolve_fl_procedure would be the right place
to do this fixup, but this is invoked only later from resolve_symbol.
Another attempt to put a fix directly after the recursive call to
resolve_symbol for sym->result lead to frightening regressions in
the testsuite, so I stayed with the attached simple solution.

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

Thanks,
Harald

From 15810999b2f5cb4d8fbd69cb488c9b0c58e6 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Wed, 6 Dec 2023 20:42:27 +0100
Subject: [PATCH] Fortran: function returning contiguous class array [PR105543]

gcc/fortran/ChangeLog:

	PR fortran/105543
	* resolve.cc (resolve_symbol): For a CLASS-valued function having a
	RESULT clause, ensure that attr.class_ok is set for its symbol as
	well as for its resolved result variable.

gcc/testsuite/ChangeLog:

	PR fortran/105543
	* gfortran.dg/contiguous_13.f90: New test.
---
 gcc/fortran/resolve.cc  |  5 +
 gcc/testsuite/gfortran.dg/contiguous_13.f90 | 22 +
 2 files changed, 27 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/contiguous_13.f90

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 166b702cd9a..4fe0e7202e5 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -16102,6 +16102,11 @@ resolve_symbol (gfc_symbol *sym)
   specification_expr = saved_specification_expr;
 }

+  /* For a CLASS-valued function with a result variable, affirm that it has
+ been resolved also when looking at the symbol 'sym'.  */
+  if (mp_flag && sym->ts.type == BT_CLASS && sym->result->attr.class_ok)
+sym->attr.class_ok = sym->result->attr.class_ok;
+
   if (sym->ts.type == BT_CLASS && sym->attr.class_ok && sym->ts.u.derived
   && CLASS_DATA (sym))
 {
diff --git a/gcc/testsuite/gfortran.dg/contiguous_13.f90 b/gcc/testsuite/gfortran.dg/contiguous_13.f90
new file mode 100644
index 000..8c6784432c9
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/contiguous_13.f90
@@ -0,0 +1,22 @@
+! { dg-do compile }
+! PR fortran/105543 - function returning contiguous class array
+! Contributed by martin 
+
+module func_contiguous
+  implicit none
+  type :: a
+  end type a
+contains
+  function create1 () result(x)
+class(a), dimension(:), contiguous, pointer :: x
+  end
+  function create2 ()
+class(a), dimension(:), contiguous, pointer :: create2
+  end
+  function create3 () result(x)
+class(*), dimension(:), contiguous, pointer :: x
+  end
+  function create4 ()
+class(*), dimension(:), contiguous, pointer :: create4
+  end
+end module func_contiguous
--
2.35.3



[PATCH] Fortran: allow NULL() for POINTER, OPTIONAL, CONTIGUOUS dummy [PR111503]

2023-12-08 Thread Harald Anlauf
Dear all,

here's another fix for the CONTIGUOUS attribute: NULL() should
derive its characteristics from its MOLD argument; otherwise it is
"determined by the entity with which the reference is associated".
(F2018:16.9.144).

The testcase is cross-checked with Intel.
NAG rejects cases where MOLD is a pointer.  I think it is wrong here.

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

Thanks,
Harald

From c73b248ec16388ed1ce109fce8a468a87e367085 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Fri, 8 Dec 2023 11:11:08 +0100
Subject: [PATCH] Fortran: allow NULL() for POINTER, OPTIONAL, CONTIGUOUS dummy
 [PR111503]

gcc/fortran/ChangeLog:

	PR fortran/111503
	* expr.cc (gfc_is_simply_contiguous): Determine characteristics of
	NULL() from MOLD argument if present, otherwise treat as present.
	* primary.cc (gfc_variable_attr): Derive attributes of NULL(MOLD)
	from MOLD.

gcc/testsuite/ChangeLog:

	PR fortran/111503
	* gfortran.dg/contiguous_14.f90: New test.
---
 gcc/fortran/expr.cc | 14 
 gcc/fortran/primary.cc  |  4 ++-
 gcc/testsuite/gfortran.dg/contiguous_14.f90 | 39 +
 3 files changed, 56 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/contiguous_14.f90

diff --git a/gcc/fortran/expr.cc b/gcc/fortran/expr.cc
index c668baeef8c..709f3c3cbef 100644
--- a/gcc/fortran/expr.cc
+++ b/gcc/fortran/expr.cc
@@ -5958,6 +5958,20 @@ gfc_is_simply_contiguous (gfc_expr *expr, bool strict, bool permit_element)
   if (expr->expr_type == EXPR_ARRAY)
 return true;

+  if (expr->expr_type == EXPR_NULL)
+{
+  /* F2018:16.9.144  NULL ([MOLD]):
+	 "If MOLD is present, the characteristics are the same as MOLD."
+	 "If MOLD is absent, the characteristics of the result are
+	 determined by the entity with which the reference is associated."
+	 F2018:15.3.2.2 characteristics attributes include CONTIGUOUS.  */
+  if (expr->ts.type == BT_UNKNOWN)
+	return true;
+  else
+	return (gfc_variable_attr (expr, NULL).contiguous
+		|| gfc_variable_attr (expr, NULL).allocatable);
+}
+
   if (expr->expr_type == EXPR_FUNCTION)
 {
   if (expr->value.function.isym)
diff --git a/gcc/fortran/primary.cc b/gcc/fortran/primary.cc
index 7278932b634..f8a1c09d190 100644
--- a/gcc/fortran/primary.cc
+++ b/gcc/fortran/primary.cc
@@ -2627,7 +2627,9 @@ gfc_variable_attr (gfc_expr *expr, gfc_typespec *ts)
   gfc_component *comp;
   bool has_inquiry_part;

-  if (expr->expr_type != EXPR_VARIABLE && expr->expr_type != EXPR_FUNCTION)
+  if (expr->expr_type != EXPR_VARIABLE
+  && expr->expr_type != EXPR_FUNCTION
+  && !(expr->expr_type == EXPR_NULL && expr->ts.type != BT_UNKNOWN))
 gfc_internal_error ("gfc_variable_attr(): Expression isn't a variable");

   sym = expr->symtree->n.sym;
diff --git a/gcc/testsuite/gfortran.dg/contiguous_14.f90 b/gcc/testsuite/gfortran.dg/contiguous_14.f90
new file mode 100644
index 000..21e42311e9c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/contiguous_14.f90
@@ -0,0 +1,39 @@
+! { dg-do compile }
+! PR fortran/111503 - passing NULL() to POINTER, OPTIONAL, CONTIGUOUS dummy
+
+program test
+  implicit none
+  integer, pointer, contiguous :: p(:) => null()
+  integer, allocatable, target :: a(:)
+  type t
+ integer, pointer, contiguous :: p(:) => null()
+ integer, allocatable :: a(:)
+  end type t
+  type(t),   target :: z
+  class(t), allocatable, target :: c
+  print *, is_contiguous (p)
+  allocate (t :: c)
+  call one (p)
+  call one ()
+  call one (null ())
+  call one (null (p))
+  call one (a)
+  call one (null (a))
+  call one (z% p)
+  call one (z% a)
+  call one (null (z% p))
+  call one (null (z% a))
+  call one (c% p)
+  call one (c% a)
+  call one (null (c% p))
+  call one (null (c% a))
+contains
+  subroutine one (x)
+integer, pointer, optional, contiguous, intent(in) :: x(:)
+print *, present (x)
+if (present (x)) then
+   print *, "->", associated (x)
+   if (associated (x)) stop 99
+end if
+  end subroutine one
+end
--
2.35.3



Re: [PATCH 1/8] fortran: Add tests covering inline MINLOC/MAXLOC without DIM [PR90608]

2024-08-05 Thread Harald Anlauf

Hi Mikael,

I had only a quick glance at this patch, but am a little concerned
about the tests involving nans.

E.g.:


+  subroutine check_all_nans()
+real, allocatable :: a(:,:,:)
+real :: nan
+integer, allocatable :: m(:)
+nan = 0
+nan = nan / nan
+allocate(a(3,3,3), source = nan)
+m = maxloc(a)
+if (size(m, dim=1) /= 3) stop 161
+if (any(m /= (/ 1, 1, 1 /))) stop 162
+  end subroutineT


Is there a reason you do not use the ieee intrinsic module way
to get a quiet nan?  Otherwise, how do you prevent exceptions
to happen, possibly leading to a failing test?
(The test cases need a workaround to run with NAG).

Thanks,
Harald





Re: [PATCH 0/8] fortran: Inline MINLOC/MAXLOC without DIM argument [PR90608]

2024-08-06 Thread Harald Anlauf

Hi Mikael,

thanks for this nice set of patches!

I've played around a bit, and it seems to look good.

I have only minor comments left (besides the nan issue raised):

- inline expansion is inhibited at -Os.  But wouldn't it be good if
  we make this expansion also dependent on -ffrontend-optimize?
  (This was the case for rank-1 before your patch).

- in the case where two sets of loop(nest)s are generated, i.e. for
  non-integral argument x, I wonder if the predictors for conditionals
  (-> _likely/_unlikely) are chosen optimally.  E.g. for this code:

subroutine minloc_real (x, m, back)
  implicit none
  real, intent(in), contiguous :: x(:)
  integer  :: m(*)
  logical, optional:: back
  m(1:rank(x)) = minloc (x,back=back)
end

the first loop becomes:

  S.10 = second_loop_entry.9 ? idx0.7 : 1;
  while (1)
{
  if (S.10 > D.4310) goto L.3;
  if (__builtin_expect ((integer(kind=8)) ((*x.0)[S.10 * D.4314 
+ D.4309] <= limit.8), 0, 8))

{
  limit.8 = (*x.0)[S.10 * D.4314 + D.4309];
  pos0.5 = S.10 + offset0.6;
  idx0.7 = S.10;
  second_loop_entry.9 = 1;
  goto L.1;
}
  S.10 = S.10 + 1;
}

This results from this code in trans-intrinsic.cc:

  if (!lab1 || HONOR_NANS (DECL_MODE (limit)))
{
  ...
  cond = gfc_unlikely (cond, PRED_BUILTIN_EXPECT);
  ifbody = build3_v (COND_EXPR, cond, ifbody,
 build_empty_stmt (input_location));
}

As the reason for this separate loop is finding a first non-nan value,
I would expect gfc_likely to be more reasonable for the common case.

(There is also the oddity S.10 = second_loop_entry.9 ? ..., where
idx0.7 seems to be not initialized, but luckily it seems to be
handled by the optimizer and seen that this is no problem.)

Having gfc_unlikely in the second set of loops is fine, as this passes
over all array elements.

Note that this is pre-existing without/before your patch, but since you
are at it, you may want to check.

Otherwise this is fine for mainline with the said issues considered.

Thanks for the patch-set!

Harald

Am 31.07.24 um 22:07 schrieb Mikael Morin:

From: Mikael Morin 

This series of patches enable the generation of inline code for the MINLOC
and MAXLOC intrinsics, when the DIM argument is not present.  The
generated code is based on the inline implementation already generated in
the scalar case, that is when ARRAY has rank 1 and DIM is present.  The
code is extended by using several variables (one for each dimension) where
the scalar code used just one, and collecting the variables to an array
before returning.

The patches are split in a way that allows inlining in more and more cases
as controlled by the gfc_inline_intrinsic_p predicate which evolves with
the patches.

They have been generated on top of the patch:
https://gcc.gnu.org/pipermail/gcc-patches/2024-July/657959.html

Mikael Morin (8):
   fortran: Add tests covering inline MINLOC/MAXLOC without DIM [PR90608]
   fortran: Disable frontend passes for inlinable MINLOC/MAXLOC [PR90608]
   fortran: Inline MINLOC/MAXLOC with no DIM and ARRAY of rank 1
 [PR90608]
   fortran: Outline array bound check generation code
   fortran: Inline integral MINLOC/MAXLOC with no DIM and no MASK
 [PR90608]
   fortran: Inline integral MINLOC/MAXLOC with no DIM and scalar MASK
 [PR90608]
   fortran: Inline non-character MINLOC/MAXLOC with no DIM [PR90608]
   fortran: Continue MINLOC/MAXLOC second loop where the first stopped
 [PR90608]

  gcc/fortran/frontend-passes.cc|   3 +-
  gcc/fortran/trans-array.cc| 382 ---
  gcc/fortran/trans-intrinsic.cc| 454 +-
  gcc/testsuite/gfortran.dg/maxloc_7.f90| 220 +
  gcc/testsuite/gfortran.dg/maxloc_bounds_4.f90 |   4 +-
  gcc/testsuite/gfortran.dg/maxloc_bounds_5.f90 |   4 +-
  gcc/testsuite/gfortran.dg/maxloc_bounds_6.f90 |   4 +-
  gcc/testsuite/gfortran.dg/maxloc_bounds_7.f90 |   4 +-
  .../gfortran.dg/maxloc_with_mask_1.f90| 393 +++
  gcc/testsuite/gfortran.dg/minloc_8.f90| 220 +
  .../gfortran.dg/minloc_with_mask_1.f90| 392 +++
  11 files changed, 1792 insertions(+), 288 deletions(-)
  create mode 100644 gcc/testsuite/gfortran.dg/maxloc_7.f90
  create mode 100644 gcc/testsuite/gfortran.dg/maxloc_with_mask_1.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minloc_8.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minloc_with_mask_1.f90






Re: [Patch, Fortran] Bug 109105 - Error-prone format string building in resolve.cc

2024-08-06 Thread Harald Anlauf

Hi Jerry,

this is OK for mainline.

I have no reservations against a backport after a waiting period.
If Roland is fine with it and nobody else objects, 14-branch might
be ok.

Thanks for the patch!

Harald

Am 06.08.24 um 21:52 schrieb Jerry D:

Hi all,

The attached patch changes all the snprintf calls to regular gfc_error 
calls to cleanup translation.  I introduced a simple macro to facilitate 
doing the checks that were being done in the bad_op code section.


 From the description for the call to gfc_extend_expr interfaces are 
mentioned so I used the CHECK_INTERFACES name for the macro.


Regression tested on linux-x86_64. No new test cases.

OK for mainline?  Backport?

Regards,

Jerry

Author: Jerry DeLisle 
Date:   Tue Aug 6 12:47:30 2024 -0700

     Fortran: Eliminate error prone translations.

     PR fortran/109105

     gcc/fortran/ChangeLog:

     * resolve.cc (CHECK_INTERFACES): New helper macro.
     (resolve_operator): Replace use of snprintf with
     gfc_error.





Re: [PATCH 0/8] fortran: Inline MINLOC/MAXLOC without DIM argument [PR90608]

2024-08-07 Thread Harald Anlauf

Hi Mikael, Thomas!

Am 07.08.24 um 11:11 schrieb Mikael Morin:

Hello,

Le 06/08/2024 à 22:57, Thomas Koenig a écrit :

Hi Mikael and Harald,


- inline expansion is inhibited at -Os.  But wouldn't it be good if
   we make this expansion also dependent on -ffrontend-optimize?
   (This was the case for rank-1 before your patch).


By the way, I disabled the minmaxloc frontend optimization without too 
much thought, because it was preventing me from seeing the effects of my 
patches in the dumps.  Now that both of you have put some focus on it, I 
think the optimization should be completely removed instead, because the 
patches make it unreachable.



The original idea was to have -ffrontend-optimize as a check if anything
went wrong with front-end optimization in particular - if the bug went
away with -fno-frontend-optimize, we knew where to look (and I knew
I had to look).

It also provides a way for users to workaround bugs in frontend 
optimizations.  If inline expansion were dependent on the flag, it would 
also provide the same benefit, but it would be using the flag outside of 
its intended scope, so I would rather not do it.



So, probably better to not do this at -Os.  One thought: Should we
also do the inlining without optimization?


At -Os: no inline expansion.  Don't we all agree on that?
I'm fine with also disabling expansion at -O0.


The following change to patch 2/8 does what I had in mind:

diff --git a/gcc/fortran/trans-intrinsic.cc b/gcc/fortran/trans-intrinsic.cc
index 9f3c3ce47bc..cc0d00f4e39 100644
--- a/gcc/fortran/trans-intrinsic.cc
+++ b/gcc/fortran/trans-intrinsic.cc
@@ -11650,6 +11650,29 @@ gfc_inline_intrinsic_function_p (gfc_expr *expr)
 case GFC_ISYM_TRANSPOSE:
   return true;

+case GFC_ISYM_MINLOC:
+case GFC_ISYM_MAXLOC:
+  {
+   /* Disable inline expansion if code size matters.  */
+   if (optimize_size)
+ return false;

/* Disable inline expansion if frontend optimization is disabled.  */
if (!flag_frontend_optimize)
  return false;


As a result, the following happens:

- at -Os, inlining will never happen (as you had it)
- at -O0, the default is -fno-frontend-optimize, and we get the
  library implementation.  Inlining is forced with -ffrontend-optimize.
- at higher -Ox, the default is -ffrontend-optimize.

I believe this is also what Thomas' original motivation was.

(This flag actually helps to see that the inlining code in gcc-14
is currently broken for minloc/maxloc and optinional back argument).

As we are not planning to remove the library implementation (-Os!),
this is also the best way to compare library to inline code.

Cheers,
Harald


Mikael






Re: [PATCH 0/8] fortran: Inline MINLOC/MAXLOC without DIM argument [PR90608]

2024-08-08 Thread Harald Anlauf

Am 08.08.24 um 19:13 schrieb Thomas Koenig:

Am 08.08.24 um 11:09 schrieb Mikael Morin:


As we are not planning to remove the library implementation (-Os!),
this is also the best way to compare library to inline code.


This makes perfect sense, but why reuse the -ffrontend-optimize option?
The manual describes it as:
This option performs front-end optimization, based on manipulating 
parts the Fortran parse tree


These patches are about inlining, there is no manipulation of the 
parse tree.  So I would rather use a separate option 
(-finline-intrinsics?).


I concur, -ffrontend-optimize should remain specific to manipulating
the parse tree.

Having a -finline-intrinsic options, which would be set at any
optimization level except -Os, may be the right way forward.

Or something else :-)


Well, I am not so convinced that -finline-intrinsics is a good choice.
What do you think users will expect from it?


Quoting from the current documentation:

-ffrontend-optimize

This option performs front-end optimization, based on manipulating 
parts the Fortran parse tree. Enabled by default by any -O option except 
-O0 and -Og. Optimizations enabled by this option include:


inlining calls to MATMUL,
elimination of identical function calls within expressions,
removing unnecessary calls to TRIM in comparisons and assignments,
replacing TRIM(a) with a(1:LEN_TRIM(a)) and
short-circuiting of logical operators (.AND. and .OR.).

It can be deselected by specifying -fno-frontend-optimize.


So we currently already do selective inlining, which we extend to
more intrinsics, and may further extend in the future.

But if you think we really need a new option I'm fine with it.

Harald


Best regards

 Thomas






[PATCH, committed] Fortran: silence Wmaybe-uninitialized warnings for LTO build [PR116221]

2024-08-11 Thread Harald Anlauf
Dear all,

I've pushed the attached simple patch for initialization of local variables
to silence warnings for LTO builds after Sam James' confirmation as

https://gcc.gnu.org/g:2b23a444bcf7eb67cb04b431d8fd4fa6f65222de

Thanks,
Harald

From 2b23a444bcf7eb67cb04b431d8fd4fa6f65222de Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Sun, 11 Aug 2024 20:31:13 +0200
Subject: [PATCH] Fortran: silence Wmaybe-uninitialized warnings for LTO build
 [PR116221]

	PR fortran/116221

gcc/fortran/ChangeLog:

	* intrinsic.cc (gfc_get_intrinsic_sub_symbol): Initialize variable.
	* symbol.cc (gfc_get_ha_symbol): Likewise.
---
 gcc/fortran/intrinsic.cc | 2 +-
 gcc/fortran/symbol.cc| 2 +-
 2 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/gcc/fortran/intrinsic.cc b/gcc/fortran/intrinsic.cc
index 40f4c4f4b0b..62c349da7f6 100644
--- a/gcc/fortran/intrinsic.cc
+++ b/gcc/fortran/intrinsic.cc
@@ -131,7 +131,7 @@ gfc_type_abi_kind (bt type, int kind)
 gfc_symbol *
 gfc_get_intrinsic_sub_symbol (const char *name)
 {
-  gfc_symbol *sym;
+  gfc_symbol *sym = NULL;

   gfc_get_symbol (name, gfc_intrinsic_namespace, &sym);
   sym->attr.always_explicit = 1;
diff --git a/gcc/fortran/symbol.cc b/gcc/fortran/symbol.cc
index b5143d9f790..a8b623dd92a 100644
--- a/gcc/fortran/symbol.cc
+++ b/gcc/fortran/symbol.cc
@@ -3599,7 +3599,7 @@ int
 gfc_get_ha_symbol (const char *name, gfc_symbol **result)
 {
   int i;
-  gfc_symtree *st;
+  gfc_symtree *st = NULL;

   i = gfc_get_ha_sym_tree (name, &st);

--
2.35.3



Re: [Fortran, Patch, PR102973, v1] Reset flag for parsing proc_ptrs in associate in error case

2024-08-13 Thread Harald Anlauf

Hi Andre,

Am 13.08.24 um 15:15 schrieb Andre Vehreschild:

Hi all,

attached patch is the last one the meta-bug 87477 ASSOCIATE depends on. The
resolution was already given in the PR, so I just beautified it and made patch
for it. I tried to come up with a testcase as well as Harald has, but had no
luck with it. I see less harm in reseting the flag in the error case than not
to do it.


this is much simpler than Berhhard's patch while functionally equivalent
and good for mainline.

Thanks for taking care of the issue!

Harald


Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?

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




[PATCH] Fortran: reject array constructor value of abstract type [PR114308]

2024-08-13 Thread Harald Anlauf
Dear all,

the attached patch checks whether the declared type of an array constructor
value is abstract, which is forbidden by the standard.
Steve found the relevant constraint in F2023, but it exists already in F2018.

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

Thanks,
Harald

From 9988d7e004796ab531df7bcda45788a7aa9276d7 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 13 Aug 2024 19:17:36 +0200
Subject: [PATCH] Fortran: reject array constructor value of abstract type
 [PR114308]

gcc/fortran/ChangeLog:

	PR fortran/114308
	* array.cc (resolve_array_list): Reject array constructor value if
	its declared type is abstract (F2018:C7114).

gcc/testsuite/ChangeLog:

	PR fortran/114308
	* gfortran.dg/abstract_type_10.f90: New test.

Co-Authored-By: Steven G. Kargl 
---
 gcc/fortran/array.cc  | 13 
 .../gfortran.dg/abstract_type_10.f90  | 30 +++
 2 files changed, 43 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/abstract_type_10.f90

diff --git a/gcc/fortran/array.cc b/gcc/fortran/array.cc
index 79c774d59a0..a5e94f1fa77 100644
--- a/gcc/fortran/array.cc
+++ b/gcc/fortran/array.cc
@@ -2127,6 +2127,19 @@ resolve_array_list (gfc_constructor_base base)
 		 "polymorphic [F2008: C4106]", &c->expr->where);
 	  t = false;
 	}
+
+  /* F2018:C7114 The declared type of an ac-value shall not be abstract.  */
+  if (c->expr->ts.type == BT_CLASS
+	  && c->expr->ts.u.derived
+	  && c->expr->ts.u.derived->attr.abstract
+	  && CLASS_DATA (c->expr))
+	{
+	  gfc_error ("Array constructor value %qs at %L is of the ABSTRACT "
+		 "type %qs", c->expr->symtree->name, &c->expr->where,
+		 CLASS_DATA (c->expr)->ts.u.derived->name);
+	  t = false;
+	}
+
 }

   return t;
diff --git a/gcc/testsuite/gfortran.dg/abstract_type_10.f90 b/gcc/testsuite/gfortran.dg/abstract_type_10.f90
new file mode 100644
index 000..a4bf65d4e12
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/abstract_type_10.f90
@@ -0,0 +1,30 @@
+! { dg-do compile }
+!
+! PR fortran/114308 - reject array constructor value of abstract type
+
+module my_module
+  implicit none
+  private
+
+  type, abstract, public :: a
+  end type
+
+  type, extends(a), public :: b
+  end type
+end
+
+program main
+  use my_module
+  implicit none
+  type(b)   :: b_instance
+  class(a), allocatable :: a_array(:)
+  class(b), allocatable :: b_array(:)
+
+  a_array = [b_instance]
+  b_array = [b_instance]
+  a_array = [a_array] ! { dg-error "is of the ABSTRACT type" }
+  a_array = [a_array(1)]  ! { dg-error "is of the ABSTRACT type" }
+  a_array = [a_array, b_instance] ! { dg-error "is of the ABSTRACT type" }
+  a_array = [b_instance, a_array] ! { dg-error "is of the ABSTRACT type" }
+  b_array = [b_array, a_array]! { dg-error "is of the ABSTRACT type" }
+end program
--
2.35.3



Re: [PATCH] Fortran: reject array constructor value of abstract type [PR114308]

2024-08-13 Thread Harald Anlauf

Pushed after an OK by Steve in the PR as

r15-2902-g9988d7e004796ab531df7bcda45788a7aa9276d7

Am 13.08.24 um 19:25 schrieb Harald Anlauf:

Dear all,

the attached patch checks whether the declared type of an array constructor
value is abstract, which is forbidden by the standard.
Steve found the relevant constraint in F2023, but it exists already in F2018.

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

Thanks,
Harald



Cheers,
Harald




[PATCH] Fortran: fix minor frontend GMP leaks

2024-08-13 Thread Harald Anlauf
Dear all,

while running f951 under valgrind on testcase gfortran.dg/sizeof_6.f90
I found two minor memleaks with GMP variables that were not cleared.

Regtested on x86_64-pc-linux-gnu.

I intend to commit to mainline soon unless there are comments.

(And no, this does not address the recent intermittent runtime failures
reported in pr116261).

Thanks,
Harald

From 0cef868a87050c9854ac17c5a604c1aa72ea1862 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 13 Aug 2024 21:17:45 +0200
Subject: [PATCH] Fortran: fix minor frontend GMP leaks

gcc/fortran/ChangeLog:

	* simplify.cc (gfc_simplify_sizeof): Clear used gmp variable.
	* target-memory.cc (gfc_target_expr_size): Likewise.
---
 gcc/fortran/simplify.cc  | 10 +++---
 gcc/fortran/target-memory.cc |  2 ++
 2 files changed, 9 insertions(+), 3 deletions(-)

diff --git a/gcc/fortran/simplify.cc b/gcc/fortran/simplify.cc
index 8ddd491de11..953d59efd70 100644
--- a/gcc/fortran/simplify.cc
+++ b/gcc/fortran/simplify.cc
@@ -7778,9 +7778,13 @@ gfc_simplify_sizeof (gfc_expr *x)
 	  || x->ts.u.cl->length->expr_type != EXPR_CONSTANT))
 return NULL;

-  if (x->rank && x->expr_type != EXPR_ARRAY
-  && !gfc_array_size (x, &array_size))
-return NULL;
+  if (x->rank && x->expr_type != EXPR_ARRAY)
+{
+  if (!gfc_array_size (x, &array_size))
+	return NULL;
+
+  mpz_clear (array_size);
+}

   result = gfc_get_constant_expr (BT_INTEGER, gfc_index_integer_kind,
   &x->where);
diff --git a/gcc/fortran/target-memory.cc b/gcc/fortran/target-memory.cc
index a02db7a06e4..0a289f32d37 100644
--- a/gcc/fortran/target-memory.cc
+++ b/gcc/fortran/target-memory.cc
@@ -158,6 +158,8 @@ gfc_target_expr_size (gfc_expr *e, size_t *size)
 	asz = mpz_get_ui (tmp);
   else
 	return false;
+
+  mpz_clear (tmp);
 }
   else
 asz = 1;
--
2.35.3



Re: [PATCH] Fortran: fix minor frontend GMP leaks

2024-08-14 Thread Harald Anlauf

Hi Andre,

Am 14.08.24 um 07:53 schrieb Andre Vehreschild:

Hi Harald,

I had a hard time to figure why this is correct, when gfc_array_size() returned
false, but now I get it. Ok to commit.


I know that reading code is always twice as hard as writing it... ;-)

Thanks for checking.  Pushed as r15-2917-ga82c4dfe52dac3 .

Harald


- Andre

On Tue, 13 Aug 2024 21:25:31 +0200
Harald Anlauf  wrote:


Dear all,

while running f951 under valgrind on testcase gfortran.dg/sizeof_6.f90
I found two minor memleaks with GMP variables that were not cleared.

Regtested on x86_64-pc-linux-gnu.

I intend to commit to mainline soon unless there are comments.

(And no, this does not address the recent intermittent runtime failures
reported in pr116261).

Thanks,
Harald




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





Re: [Fortran, Patch, PR110033, v1] Fix associate for coarrays

2024-08-14 Thread Harald Anlauf

Hi Andre,

Am 12.08.24 um 14:11 schrieb Andre Vehreschild:

Hi all,

the attached two patches fix ASSOCIATE for coarrays, i.e. that a coarray
associated to a variable is also a coarray in the block of the ASSOCIATE
command. The patch has two parts:

1. pr110033p1_1.patch: Adds a corank member to the gfc_expr structure. I
decided to add it here and keep track of the corank of an expression, because
calling gfc_get_corank was getting to expensive with the associate patch. This
patch also improves the usage of coarrays in select type/rank constructs.

2. pr110033p2_1.patch: The changes and testcase for PR 110033. In essence the
coarray is not detected correctly on the expression to associate to and
therefore not propagated correctly into the block of the ASSOCIATE command. The
patch adds correct treatment for propagating the coarray token into the block,
too.

The costs of tracking the corank along side to the rank of an expression are
about 30 seconds real user time (i.e. time's "real" row) on a rather old Intel
i7-5775C@3.3GHz  with 24G RAM that was used for work during the test. If need be
I can tuned that more.

Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?


Paul already gave a basic OK, and I won't object.

However, the testcase should be fixed.  It is only correct for
single-image runs!  (Verified with Intel ifx).

You have:

  associate (y => x)
y = -1
y[1] = 35
  end associate

and check:

  if (x /= 35) stop 1

This should rather be

  if (x[1] /= 35) stop 1

or for number of images > 1:

  if (this_image() == 1) then
 if (x /= 35) stop 1
  else
 if (x /= -1) stop 99
  end if

and similarly

  if (.NOT. c%l) stop 3

needs to be adjusted accordingly.

Thanks,
Harald


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




Re: [Fortran, Patch, PR110033, v1] Fix associate for coarrays

2024-08-15 Thread Harald Anlauf

Hi Andre,

Am 15.08.24 um 17:35 schrieb Andre Vehreschild:

Hi Harald, hi Paul,

thanks for the ok and the suggestions/recommendations on the testcase. I added
that and commit as: gcc-15-2935-gdbf4c574b92


I didn't notice this while skimming over the patch, but
gcc-testresults has:

../../src-master/gcc/fortran/resolve.cc: In function ‘bool
resolve_operator(gfc_expr*)’:
../../src-master/gcc/fortran/resolve.cc:4649:22: error: too many
arguments for format [-Werror=format-extra-args]
 4649 |   gfc_error ("Inconsistent coranks for operator at %%L
and %%L",
  |
^~


The format strings should have contained %L's, not %%L.

A follow-up fix is pre-approved.

Cheers,
Harald



[PATCH] Fortran: fix doumentation of intrinsic RANDOM_INIT [PR114146]

2024-08-15 Thread Harald Anlauf
Dear all,

here's a documentation bugfix.  The previous wording was in conflict
with the standard, while the runtime behavior is apparently fine.

Checked with make dvi pdf .

OK for mainline?

Thanks,
Harald

From 4515018fd858fb6ae98b54d507596ef123d7580e Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Thu, 15 Aug 2024 22:31:11 +0200
Subject: [PATCH] Fortran: fix doumentation of intrinsic RANDOM_INIT [PR114146]

gcc/fortran/ChangeLog:

	* intrinsic.texi: Fix documentation of arguments of RANDOM_INIT,
	which is conforming to the F2018 standard.
---
 gcc/fortran/intrinsic.texi | 12 ++--
 1 file changed, 6 insertions(+), 6 deletions(-)

diff --git a/gcc/fortran/intrinsic.texi b/gcc/fortran/intrinsic.texi
index 3d3b9edf8e6..10683e1185d 100644
--- a/gcc/fortran/intrinsic.texi
+++ b/gcc/fortran/intrinsic.texi
@@ -11928,15 +11928,15 @@ Subroutine
 and it is @code{INTENT(IN)}.  If it is @code{.true.}, the seed is set to
 a processor-dependent value that is the same each time @code{RANDOM_INIT}
 is called from the same image.  The term ``same image'' means a single
-instance of program execution.  The sequence of random numbers is different
-for repeated execution of the program.  If it is @code{.false.}, the seed
-is set to a processor-dependent value.
+instance of program execution.  The sequence of random numbers is the same
+for repeated execution of the program with the same execution environment.
+If it is @code{.false.}, the seed is set to a processor-dependent value.
 @item @var{IMAGE_DISTINCT} @tab Shall be a scalar with a
 @code{LOGICAL} type, and it is @code{INTENT(IN)}.  If it is @code{.true.},
-the seed is set to a processor-dependent value that is distinct from th
+the seed is set to a processor-dependent value that is distinct from the
 seed set by a call to @code{RANDOM_INIT} in another image.  If it is
-@code{.false.}, the seed is set to a value that does depend which image called
-@code{RANDOM_INIT}.
+@code{.false.}, the seed is set to a value that is the same on every image
+calling @code{RANDOM_INIT}.
 @end multitable

 @item @emph{Example}:
--
2.35.3



Re: [PATCH] Fortran: fix doumentation of intrinsic RANDOM_INIT [PR114146]

2024-08-16 Thread Harald Anlauf

Hi Andre,

Am 16.08.24 um 07:46 schrieb Andre Vehreschild:

Hi Harald,

s/doumentation/documentation/

in the commit's title.


oops!  Thanks for pointing this out.

Fixed and pushed as r15-2955-g07ece73d4712c6 .

Harald


Thanks for the patch, ok to commit.

- Andre

On Thu, 15 Aug 2024 22:37:53 +0200
Harald Anlauf  wrote:


Dear all,

here's a documentation bugfix.  The previous wording was in conflict
with the standard, while the runtime behavior is apparently fine.

Checked with make dvi pdf .

OK for mainline?

Thanks,
Harald




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





Re: [Fortran, Patch, PR46371, v1] Fix coarrays use in select type

2024-08-16 Thread Harald Anlauf

Hi Andre,

Am 16.08.24 um 14:10 schrieb Andre Vehreschild:

Hi all,

attached patch is a follow up on the pr110033 patch and fixes two ICEs
reported in pr46371. With the patch also pr56496 is fixed, although that could
have been fixed by pr110033 already. I just added the testcase from pr56496 here
as coarray/select_type_3.f90 (I like it when the name of the test gives a rough
idea on what is tested instead of having just the pr#) to have it covered.

Bootstraps and regtests ok on x86_64-pc-linux-gnu. Ok for mainline?


this looks good to me.

I think with this patch also pr99837 is resolved.  Can you have a look,
and if so, close it?

Thanks for the patch!

Harald


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




Re: [Ping x 3, Patch, Fortran, PR84244, v3] Fix ICE in recompute_tree_invariant_for_addr_expr, at tree.c:4535

2024-08-16 Thread Harald Anlauf

Hi Andre,

Am 16.08.24 um 12:05 schrieb Andre Vehreschild:

Hi all,

any one for a review? This patch is over a month old and starts to rot.

Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?


this is good to go.

Thanks for the patch!

Harald


- Andre

On Fri, 9 Aug 2024 16:27:42 +0200
Andre Vehreschild  wrote:


Ping!

On Wed, 17 Jul 2024 15:11:33 +0200
Andre Vehreschild  wrote:


Hi all,

and the last ping.

Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?

Regards,
Andre

On Thu, 11 Jul 2024 16:05:09 +0200
Andre Vehreschild  wrote:


Hi all,

the attached patch fixes a segfault in the compiler, where for pointer
components of a derived type the caf_token in the component was not
set, when the derived was previously used outside of a coarray.

Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?

Regards,
Andre



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



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



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




Re: [PATCH v2 10/10] fortran: Add -finline-intrinsics flag for MINLOC/MAXLOC [PR90608]

2024-08-19 Thread Harald Anlauf

Hi Mikael,

apart from patch #04/10, which did not apply cleanly here, I was
able to test your patch.  It seems to work with a manual workaround
(-fno-frontend-optimize) to work around this problem.
Might be a local issue...

That said, it works as advertised.  Thanks for separating out the
IEEE-NaN tests.

What I did not fully get is the way you deal with -finline-intrinsics= .
Currently there are only MINLOC and MAXLOC, but in the future there
could be many more intrinsics.  Given that you need 2 bits per
intrinsic in flag_inline_intrinsics, how future-proof is that?

In the documentation, you have:

+The set of intrinsics permitting the choice of implementation variant 
through
+@code{-finline-intrinsics} is currently limited to non-scalar 
@code{MAXLOC} and

+@code{MINLOC}.

Why do you say "non-scalar"?  The new inlining is done for these
intrinsics when the DIM argument is absent.  The result characteristics
however is:

  "If DIM does not appear, the result is an array of rank one and of 
size equal to the rank of ARRAY; ..."


and I thought the implementation does just that and does that right.
(With DIM present, the result is an array of rank rank(arg)-1.)
Can you clarify the wording in a way that is better understandable?

Otherwise the Fortran parts look fine to me.

For the changes to gcc/flag-types.h you might need an OK from the
gcc maintainers.

Thanks,
Harald

Am 16.08.24 um 12:22 schrieb Mikael Morin:

From: Mikael Morin 

This patch is new in the V2 series.

Regression-tested on x86_64-pc-linux-gnu.
OK for master?

-- >8 --

Introduce the -finline-intrinsics flag to control from the command line
whether to generate either inline code or calls to the functions from the
library, for the MINLOC and MAXLOC intrinsics.

The flag allows to specify inlining either independently for each intrinsic
(either MINLOC or MAXLOC), or all together.  For each intrinsic, a default
value is set if none was set.  The default value depends on the optimization
setting: inlining is avoided if not optimizing or if optimizing for size;
otherwise inlining is preferred.

There is no direct support for this behaviour provided by the .opt options
framework.  It is obtained by defining three different variants of the flag
(finline-intrinsics, fno-inline-intrinsics, finline-intrinsics=) all using
the same underlying option variable.  Each enum value (corresponding to an
intrinsic function) uses two identical bits, and the variable is initialized
with alternated bits, so that we can tell whether the value was left
initialized by checking whether the two bits have different values.

PR fortran/90608

gcc/ChangeLog:

* flag-types.h (enum gfc_inlineable_intrinsics): New type.

gcc/fortran/ChangeLog:

* invoke.texi(finline-intrinsics): Document new flag.
* lang.opt (finline-intrinsics, finline-intrinsics=,
fno-inline-intrinsics): New flags.
* options.cc (gfc_post_options): If the option variable controling
the inlining of MAXLOC (respectively MINLOC) has not been set, set
it or clear it depending on the optimization option variables.
* trans-intrinsic.cc (gfc_inline_intrinsic_function_p): Return false
if inlining for the intrinsic is disabled according to the option
variable.

gcc/testsuite/ChangeLog:

* gfortran.dg/minmaxloc_18.f90: New test.
* gfortran.dg/minmaxloc_18a.f90: New test.
* gfortran.dg/minmaxloc_18b.f90: New test.
* gfortran.dg/minmaxloc_18c.f90: New test.
* gfortran.dg/minmaxloc_18d.f90: New test.
---
  gcc/flag-types.h|  30 +
  gcc/fortran/invoke.texi |  24 +
  gcc/fortran/lang.opt|  27 +
  gcc/fortran/options.cc  |  21 +-
  gcc/fortran/trans-intrinsic.cc  |  13 +-
  gcc/testsuite/gfortran.dg/minmaxloc_18.f90  | 772 
  gcc/testsuite/gfortran.dg/minmaxloc_18a.f90 |  10 +
  gcc/testsuite/gfortran.dg/minmaxloc_18b.f90 |  10 +
  gcc/testsuite/gfortran.dg/minmaxloc_18c.f90 |  10 +
  gcc/testsuite/gfortran.dg/minmaxloc_18d.f90 |  10 +
  10 files changed, 922 insertions(+), 5 deletions(-)
  create mode 100644 gcc/testsuite/gfortran.dg/minmaxloc_18.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minmaxloc_18a.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minmaxloc_18b.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minmaxloc_18c.f90
  create mode 100644 gcc/testsuite/gfortran.dg/minmaxloc_18d.f90

diff --git a/gcc/flag-types.h b/gcc/flag-types.h
index 1e497f0bb91..df56337f7e8 100644
--- a/gcc/flag-types.h
+++ b/gcc/flag-types.h
@@ -451,6 +451,36 @@ enum gfc_convert
  };
  
  
+/* gfortran -finline-intrinsics= values;

+   We use two identical bits for each value, and initialize with alternated
+   bits, so that we can check whether a value has been set by checking whether
+   the two bits have identical value.  */
+
+#define GFC_INL_INTR_VAL(idx) (3 << (2 * 

Re: [PATCH v2 10/10] fortran: Add -finline-intrinsics flag for MINLOC/MAXLOC [PR90608]

2024-08-20 Thread Harald Anlauf

Hi Mikael,

Am 20.08.24 um 11:51 schrieb Mikael Morin:

Hello,

Le 19/08/2024 à 21:44, Harald Anlauf a écrit :

Hi Mikael,

apart from patch #04/10, which did not apply cleanly here, I was
able to test your patch.  It seems to work with a manual workaround
(-fno-frontend-optimize) to work around this problem.
Might be a local issue...

Huh? That's unexpected, patches were rebased before submitting, and I 
don't think there was any recent activity in that area of the compiler 
anyway.


staring at that patch and the code revealed that Andre's coarray rank
stuff interfered, so you might see a merge conflict.  I managed to
resolve this, and then everything passes.  Good!


That said, it works as advertised.  Thanks for separating out the
IEEE-NaN tests.

What I did not fully get is the way you deal with -finline-intrinsics= .
Currently there are only MINLOC and MAXLOC, but in the future there
could be many more intrinsics.  Given that you need 2 bits per
intrinsic in flag_inline_intrinsics, how future-proof is that?


Well, I don't expect that many candidate intrinsics for the flags; 
currently SUM and PRODUCT could be added, and probably IALL, IANY and 
IPARITY as well.  Remember that having both a libgfortran and a frontend 
implementation is a prerequisite.


Yes, these are the primary candidates.  Maybe NORM2; MINVAL, MAXVAL;
FINDLOC; CSHIFT as well.

For the future, 2 bits gives room to 16 intrinsics, and if we extend to 
64 bits, to 32 intrinsics without much hassle.  Having only 1 bit per 
intrinsic would be certainly more future proof but I haven't found how 
to do it.  Zero bit (aka no per-intrinsic setting) would be even more 
future-proof, but less convenient.  As a last resort possibility the 
.opt framework gives the possibility to accumulate options in a vector 
and have them processed "by hand".  It seemed more convenient to me to 
just use 2 bits per intrinsic, but we can fall back to manual processing 
if we get out of bits at some point.


Using only 1 bit per intrinsic was what I tried first, but then the 
default value has to be set before processing the flags, which means no 
default value depending on optimization, as optimization level is not 
known at that time.  I tried using EnabledBy(O || Ofast || Og) to set 
default value dependending on optimization, but this doesn't work either 
because the "O" covers all levels (-O0, -O1, -O2, -O3) without 
distinction.  And finally EnabledBy(O1 || O2 || O3 || Ofast || Og) is 
not accepted because "O1", "O2" and "O3" are not valid option names.


I can certainly drop the per-intrinsic setting to have unlimited room 
for future intrinsics.  Or if you have ideas on how to only use one bit 
per intrinsic, I'm all ears.  Or maybe the testcases are too cumbersome, 
and with a slight modification of behaviour we can save one bit (for 
example, also generate inline code for -O0). What do you think?


Since the logic is essentially ternary, using 2 bits is natural.
I was not sure if we would be limited to 16 intrinsics, which would
be fairly small, since I did not see what types are possible.
32 is probably good enough for the next decade or so...


In the documentation, you have:

+The set of intrinsics permitting the choice of implementation variant
through
+@code{-finline-intrinsics} is currently limited to non-scalar
@code{MAXLOC} and
+@code{MINLOC}.

Why do you say "non-scalar"?  The new inlining is done for these
intrinsics when the DIM argument is absent.  The result characteristics
however is:

   "If DIM does not appear, the result is an array of rank one and of
size equal to the rank of ARRAY; ..."

and I thought the implementation does just that and does that right.
(With DIM present, the result is an array of rank rank(arg)-1.)
Can you clarify the wording in a way that is better understandable?

Yeah, these patches are all about non-scalar MINLOC/MAXLOC.  But there 
is also the scalar MINLOC/MAXLOC case which has pre-existing inline code 
support (and on which these patches are based).  The scalar case (aka 
with DIM present, and ARRAY of rank 1) is always inlined, so the flag 
has no effect on it.


I was asking because you refer by "scalar" or "non-scalar" to the
result, not to the argument.  This looked like non-standard use of
language to me.


Does this sound better?:
The set of intrinsics allowed as argument to @code{-finline-intrinsics=} 
is currently limited to @code{MAXLOC} and @code{MINLOC}.  The effect of 
the flag is moreover limited to calls of those intrinsics without 
@code{DIM} argument and with @code{ARRAY} of a non-@code{CHARACTER} type.


Yes, this is better.  Do you want to add something like:
The case of rank-1 argument and @code{DIM} argument present, i.e.
@code{MAXLOC}(A(:),@code{DIM}=1)} or @code{MINLOC}(A(:),@code{DIM}=1)}
is inlined unconditionally for numeric rank-1 array argument A.

Tha

Re: [Fortran, Patch, PR86468, v1] Fix propagation of corank to array components in derived types.

2024-08-20 Thread Harald Anlauf

Hi Andre,

Am 20.08.24 um 13:52 schrieb Andre Vehreschild:

Hi all,

attached patch fixes an ICE in gimplify by assuring that the corank of a
non-pointer, non-coarray array component in a derived type is zero. Previously
(erroneously) the full corank of the type has been used. There is one exception
for pointer typed array components in coarray derived types. These can be
associated only to coarray array targets (compare F2018 C1024 and C1026).
Therefore for those the corank is still propagated.


the patch is OK for mainline, but the formatting violates the coding
style here:

@@ -2909,12 +2909,14 @@ gfc_get_derived_type (gfc_symbol * derived, int
codimen)
  else
akind = GFC_ARRAY_ALLOCATABLE;
  /* Pointers to arrays aren't actually pointer types.  The
-descriptors are separate, but the data is common.  */
- field_type = gfc_build_array_type (field_type, c->as, akind,
-!c->attr.target
-&& !c->attr.pointer,
-c->attr.contiguous,
-codimen);
+descriptors are separate, but the data is common.  Every
+array pointer in a coarray derived type needs to provide space
+for the coarray management, too.  Therefore treat coarrays
+and pointers to coarrays in derived types the same.  */
+ field_type = gfc_build_array_type (
^^^
Please move this opening parenthesis to the next line,
otherwise the indenting with emacs goes sideways.

+   field_type, c->as, akind, !c->attr.target && !c->attr.pointer,
+   c->attr.contiguous,
+   c->attr.codimension || c->attr.pointer ? codimen : 0);
}
  else
field_type = gfc_get_nodesc_array_type (field_type, c->as,


Thanks,
Harald


Regtests ok on x86_64-pc-linux-gnu / Fedora 39. Ok for mainline?

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




Re: [PATCH 1/2] libgfortran: Remove early return if extent is zero [PR112371]

2023-11-06 Thread Harald Anlauf

Hi Mikael,

Am 06.11.23 um 12:43 schrieb Mikael Morin:

Remove the early return present in function templates for transformational
functions doing a (masked) reduction of an array along a dimension.
This early return, which triggered if the extent in the reduction dimension
was zero, was wrong because even if the reduction operation degenerates to
a constant value in that case, one has to loop anyway along the other
dimensions to initialize every element of the resulting array with that
constant value.

The offending piece of code was present in several places, and this removes
them all.  Namely, the impacted m4 files are ifunction.m4 for regular
functions and types, ifunction-s.m4 for character minloc and maxloc, and
ifunction-s2.m4 for character minval and maxval.


I wonder if the correct fix would be to replace (instead of deleting)


diff --git a/libgfortran/m4/ifunction.m4 b/libgfortran/m4/ifunction.m4
index c64217ec5db..480649cf691 100644
--- a/libgfortran/m4/ifunction.m4
+++ b/libgfortran/m4/ifunction.m4
@@ -232,8 +232,6 @@ m'name`'rtype_qual`_'atype_code` ('rtype` * const restrict 
retarray,
  }

len = GFC_DESCRIPTOR_EXTENT(array,dim);
-  if (len <= 0)
-return;

mbase = mask->base_addr;



by the following:

  if (len < 0)
len = 0;

See ifunction.m4, lines 56ff, which check if the result of

  len = GFC_DESCRIPTOR_EXTENT(array,dim);

is negative.  I haven't tried to create a testcase, though.

Similarly for the other templates.

Thanks,
Harald



Re: [PATCH 2/2] libgfortran: Remove empty array descriptor first dimension overwrite [PR112371]

2023-11-06 Thread Harald Anlauf

Hi Mikael,

Am 06.11.23 um 12:43 schrieb Mikael Morin:

Remove the forced overwrite of the first dimension of the result array
descriptor to set it to zero extent, in the function templates for
transformational functions doing an array reduction along a dimension.  This
overwrite, which happened before early returning in case the result array
was empty, was wrong because an array may have a non-zero extent in the
first dimension and still be empty if it has a zero extent in a higher
dimension.  Overwriting the dimension was resulting in wrong array result
upper bound for the first dimension in that case.

The offending piece of code was present in several places, and this removes
them all.  More precisely, there is only one case to fix for logical
reduction functions, and there are three cases for other reduction
functions, corresponding to non-masked reduction, reduction with array mask,
and reduction with scalar mask.  The impacted m4 files are
ifunction_logical.m4 for logical reduction functions, ifunction.m4 for
regular functions and types, ifunction-s.m4 for character minloc and maxloc,
ifunction-s2.m4 for character minval and maxval, and ifindloc1.m4 for
findloc.


while your fix seems mechanical and correct, I wonder if you looked
at the following pre-existing irregularity which can be seen in
this snippet:


diff --git a/libgfortran/m4/ifunction.m4 b/libgfortran/m4/ifunction.m4
index 480649cf691..abc15b430ab 100644
--- a/libgfortran/m4/ifunction.m4
+++ b/libgfortran/m4/ifunction.m4
@@ -96,12 +96,7 @@ name`'rtype_qual`_'atype_code` ('rtype` * const restrict 
retarray,

retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
if (alloc_size == 0)
-   {
- /* Make sure we have a zero-sized array.  */
- GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
- return;
-
-   }
+   return;
  }
else
  {


This is all enclosed in a block which has
  if (retarray->base_addr == NULL)
but allocates and sets retarray->base_addr, while


@@ -290,11 +285,7 @@ m'name`'rtype_qual`_'atype_code` ('rtype` * const restrict 
retarray,
retarray->dtype.rank = rank;

if (alloc_size == 0)
-   {
- /* Make sure we have a zero-sized array.  */
- GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
- return;
-   }
+   return;
else
retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));



and


@@ -454,11 +445,7 @@ void
alloc_size = GFC_DESCRIPTOR_STRIDE(retarray,rank-1) * extent[rank-1];

if (alloc_size == 0)
-   {
- /* Make sure we have a zero-sized array.  */
- GFC_DIMENSION_SET(retarray->dim[0], 0, -1, 1);
- return;
-   }
+   return;
else
retarray->base_addr = xmallocarray (alloc_size, sizeof (rtype_name));
  }


do not set retarray->base_addr to non-NULL for alloc_size == 0.

Do you know if the first snippet can be safely rewritten to avoid
the (hopefully pointless) xmallocarray for alloc_size == 0?

Thanks,
Harald



Re: [PATCH 2/2] libgfortran: Remove empty array descriptor first dimension overwrite [PR112371]

2023-11-06 Thread Harald Anlauf

Hi Mikael,

Am 06.11.23 um 20:19 schrieb Mikael Morin:


This change to the testcase:

diff --git a/gcc/testsuite/gfortran.dg/bound_11.f90
b/gcc/testsuite/gfortran.dg/bound_11.f90
index 170eba4ddfd..2e96f843476 100644
--- a/gcc/testsuite/gfortran.dg/bound_11.f90
+++ b/gcc/testsuite/gfortran.dg/bound_11.f90
@@ -88,6 +88,7 @@ contains
  m4 = .false.
  i = 1
  r = sum(a, dim=i)
+    if (.not. allocated(r)) stop 210
  if (any(shape(r) /= (/ 3, 0, 7 /))) stop 211
  if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 212
  i = 2
@@ -104,6 +105,7 @@ contains
  if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 218
  i = 1
  r = sum(a, dim=i, mask=m1)
+    if (.not. allocated(r)) stop 220
  if (any(shape(r) /= (/ 3, 0, 7 /))) stop 221
  if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 222
  i = 2
@@ -120,6 +122,7 @@ contains
  if (any(ubound(r) /= (/ 9, 3, 0 /))) stop 228
  i = 1
  r = sum(a, dim=i, mask=m4)
+    if (.not. allocated(r)) stop 230
  if (any(shape(r) /= (/ 3, 0, 7 /))) stop 231
  if (any(ubound(r) /= (/ 3, 0, 7 /))) stop 232
  i = 2

gives me a FAIL with STOP 220 (or STOP 230 if the STOP 220 line is
commented); the first one with STOP 210 passes.
So it is the first snippet with the xmallocarray (which supports zero
values see memory.c) call that is the correct one.
Good catch, I will open a separate PR.


ah, now I see that the case of allocation of zero elements
always allocates one byte, which is needed for r.data to be
non-null.

Go ahead!

Harald



Mikael





Re: [PATCH v2 0/3] libgfortran: empty array fixes

2023-11-07 Thread Harald Anlauf

Hi Mikael,

this is OK.

Thanks for the patches!

Harald

On 11/7/23 11:24, Mikael Morin wrote:

Hello,

Harald's review of the previous version [1] of these patches spotted a possible
misbehaving case in one patch, and a latent bug in the area of the second
patch.
So here is the second try, bootstraped and regression tested on 
x86_64-pc-linux-gnu.
OK for master?

Mikael

[1]:
https://gcc.gnu.org/pipermail/fortran/2023-November/059896.html
https://gcc.gnu.org/pipermail/gcc-patches/2023-November/635305.html

Changes from version 1:
  * Add patch 1/3 to the series fixing the unallocated empty result issue.
  * In patch 2/3 (formerly 1/2) clamp negative extent to zero.


Mikael Morin (3):
   libgfortran: Don't skip allocation if size is zero [PR112412]
   libgfortran: Remove early return if extent is zero [PR112371]
   libgfortran: Remove empty array descriptor first dimension overwrite
 [PR112371]

  gcc/testsuite/gfortran.dg/allocated_4.f90 | 195 +++
  gcc/testsuite/gfortran.dg/bound_10.f90| 207 
  gcc/testsuite/gfortran.dg/bound_11.f90| 588 ++
  libgfortran/generated/all_l1.c|   9 +-
  libgfortran/generated/all_l16.c   |   9 +-
  libgfortran/generated/all_l2.c|   9 +-
  libgfortran/generated/all_l4.c|   9 +-
  libgfortran/generated/all_l8.c|   9 +-
  libgfortran/generated/any_l1.c|   9 +-
  libgfortran/generated/any_l16.c   |   9 +-
  libgfortran/generated/any_l2.c|   9 +-
  libgfortran/generated/any_l4.c|   9 +-
  libgfortran/generated/any_l8.c|   9 +-
  libgfortran/generated/count_16_l.c|   9 +-
  libgfortran/generated/count_1_l.c |   9 +-
  libgfortran/generated/count_2_l.c |   9 +-
  libgfortran/generated/count_4_l.c |   9 +-
  libgfortran/generated/count_8_l.c |   9 +-
  libgfortran/generated/findloc1_c10.c  |  18 +-
  libgfortran/generated/findloc1_c16.c  |  18 +-
  libgfortran/generated/findloc1_c17.c  |  18 +-
  libgfortran/generated/findloc1_c4.c   |  18 +-
  libgfortran/generated/findloc1_c8.c   |  18 +-
  libgfortran/generated/findloc1_i1.c   |  18 +-
  libgfortran/generated/findloc1_i16.c  |  18 +-
  libgfortran/generated/findloc1_i2.c   |  18 +-
  libgfortran/generated/findloc1_i4.c   |  18 +-
  libgfortran/generated/findloc1_i8.c   |  18 +-
  libgfortran/generated/findloc1_r10.c  |  18 +-
  libgfortran/generated/findloc1_r16.c  |  18 +-
  libgfortran/generated/findloc1_r17.c  |  18 +-
  libgfortran/generated/findloc1_r4.c   |  18 +-
  libgfortran/generated/findloc1_r8.c   |  18 +-
  libgfortran/generated/findloc1_s1.c   |  18 +-
  libgfortran/generated/findloc1_s4.c   |  18 +-
  libgfortran/generated/iall_i1.c   |  30 +-
  libgfortran/generated/iall_i16.c  |  30 +-
  libgfortran/generated/iall_i2.c   |  30 +-
  libgfortran/generated/iall_i4.c   |  30 +-
  libgfortran/generated/iall_i8.c   |  30 +-
  libgfortran/generated/iany_i1.c   |  30 +-
  libgfortran/generated/iany_i16.c  |  30 +-
  libgfortran/generated/iany_i2.c   |  30 +-
  libgfortran/generated/iany_i4.c   |  30 +-
  libgfortran/generated/iany_i8.c   |  30 +-
  libgfortran/generated/iparity_i1.c|  30 +-
  libgfortran/generated/iparity_i16.c   |  30 +-
  libgfortran/generated/iparity_i2.c|  30 +-
  libgfortran/generated/iparity_i4.c|  30 +-
  libgfortran/generated/iparity_i8.c|  30 +-
  libgfortran/generated/maxloc1_16_i1.c |  30 +-
  libgfortran/generated/maxloc1_16_i16.c|  30 +-
  libgfortran/generated/maxloc1_16_i2.c |  30 +-
  libgfortran/generated/maxloc1_16_i4.c |  30 +-
  libgfortran/generated/maxloc1_16_i8.c |  30 +-
  libgfortran/generated/maxloc1_16_r10.c|  30 +-
  libgfortran/generated/maxloc1_16_r16.c|  30 +-
  libgfortran/generated/maxloc1_16_r17.c|  30 +-
  libgfortran/generated/maxloc1_16_r4.c |  30 +-
  libgfortran/generated/maxloc1_16_r8.c |  30 +-
  libgfortran/generated/maxloc1_16_s1.c |  30 +-
  libgfortran/generated/maxloc1_16_s4.c |  30 +-
  libgfortran/generated/maxloc1_4_i1.c  |  30 +-
  libgfortran/generated/maxloc1_4_i16.c |  30 +-
  libgfortran/generated/maxloc1_4_i2.c  |  30 +-
  libgfortran/generated/maxloc1_4_i4.c  |  30 +-
  libgfortran/generated/maxloc1_4_i8.c  |  30 +-
  libgfortran/generated/maxloc1_4_r10.c |  30 +-
  libgfortran/generated/maxloc1_4_r16.c |  30 +-
  libgfortran/generated/maxloc1_4_r17.c |  30 +-
  libgfortran/generated/maxloc1_4_r4.c  |  30 +-
  libgfortran/generated/maxloc1_4_r8.c  |  30 +-
  libgfortran/generated/maxloc1_4_s1.c  |  30 +-
  libgfortran/generated/maxloc1_4_s4.c  |  30 +-
  libgfortran/generated/maxloc1_8_i1.c  |  30 +-
  libgfortran/generated/maxloc1_8_i16.c |  30 +-
  libgfortran/generated/

Re: [Patch, fortran] PR112459 - gfortran -w option causes derived-type finalization at creation time

2023-11-11 Thread Harald Anlauf

Hi Paul,

this is OK.

Thanks for the patch!

Harald

Am 11.11.23 um 11:15 schrieb Paul Richard Thomas:

Hi All,

Evidently -w causes gfc_option.allow_std to be set to default, which allows
anything and everything to happen, including these f2003/8 finalizations.
The fix is trivial.

Regtests fine - OK for mainline and -13 branch?

Paul

Fortran: Prevent unwanted finalization with -w option [PR112459]

2023-11-11  Paul Thomas  

gcc/fortran
PR fortran/112459
* trans-array.cc (gfc_trans_array_constructor_value): Replace
gfc_notification_std with explicit logical expression that
selects F2003/2008 and excludes -std=default/gnu.
*trans-array.cc (gfc_conv_expr): Ditto.

gcc/testsuite/
PR fortran/112459
* gfortran.dg/pr112459.f90: New test.






Re: [Patch] Fortran: Accept -std=f2023 support, update line-length for Fortran 2023

2023-11-16 Thread Harald Anlauf

Hi Tobias,

On 11/16/23 14:01, Tobias Burnus wrote:

This adds -std=f2023, which is mostly a prep patch for future changes.

However, Fortran 2023, https://j3-fortran.org/doc/year/23/23-007r1.pdf
changes two things which is taken
care in this patch:

(A) In "6.3.2.1 Free form line length":

Fortran 2018: "If a line consists entirely of characters of default kind
(7.4.4), it shall contain at most 132 characters"
Fortran 2023: "A line shall contain at most ten thousand characters."

(B) In "6.3.2.6 Free form statements":
Fortran 2018: "A statement shall not have more than 255 continuation
lines."
Fortran 2023: "A statement shall not have more than one million
characters."


this is really a funny change: we're not really prepared to handle
this.  According to the standard one can have 99 lines with only
"&" and then an ";", but then only 100 lines with 1 characters.

There is a similar wording for fixed-form which you overlooked:

6.3.3.5 Fixed form statements

Fortran 2023: "A statement shall not have more than one million characters"

Please adjust the fixed-form limits in your patch.

If you think that we need testcases for fixed-form, add them,
or forget them.  I don't bother.


I have not added a testcase for exceeding the latter but otherwise there
are new
tests and I had to add a couple of -std=f2018 to existing tests.

Comments, suggestions, approval?


I have the following comments:

- there are existing testcases continuation_5.f, continuation_6.f,
  thus I suggest to rename your new continuation_{5,6}.f90 to
  continuation_17.f90+ .

- I don't understand your new testcase line_length_14.f90 .
  This is supposed to test -std=gnu, but then -std=gnu is not a
  standard but a moving target, which is why you had to adjust
  existing testcases.
  So what does it buy us beyond line_length_1{2,3}.f90 ?


Tobias

PS: I find it funny that -std=c23, -std=c++23 and -std=f2023 will get
added in the same GCC release.


:-)


PPS: I did not bother adding .f23 as file extension; I believe that also
.f18 is unsupported.


I never use extensions other than .f90 for portable code.

With the above fixed, I am fine with your patch.

Thanks,
Harald


-
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




Re: [Patch] Fortran: Accept -std=f2023, update line-length for Fortran 2023

2023-11-17 Thread Harald Anlauf

Hi Tobias,

On 11/17/23 12:38, Tobias Burnus wrote:

Hi Harald, hi all,

On 16.11.23 20:30, Harald Anlauf wrote:

According to the standard one can have 99 lines with only
"&" and then an ";", but then only 100 lines with 1 characters.


I believe a single '&' is not valid, you either need '&&' or something
else + '&'; thus, you can have only half a million lines + 1.


after looking at the F2023 standard again I wonder why
they did such a disservice to compiler developers...

You are right: a single '&' is not valid.

6.3.2.4 also has:

"When used for continuation, the “&” is not part of the statement"

And 6.3.2.5 (also 6.3.3.4): "The “;” is not part of the statement".

So a million "&"-continued lines is possible in free form.

For fixed form, 6.3.3.1 has: "If a source line contains only characters
of default kind, it shall contain exactly 72 characters; otherwise, its
maximum number of characters is processor dependent."

I wonder what I should make out of this...


In the code, I still use 1,000,000 but now with a comment.


Yeah, for the time being this is the most reasonable solution.
Let's claim that the 10^6 line limit is the new GNU standard ;-)

Cheers,
Harald




[PATCH] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-18 Thread Harald Anlauf
Hi all,

Fortran 2023 added restrictions on integer arguments to SYSTEM_CLOCK.
The attached patch implements these.

I was struggling with the way we should handle features that are sort-of
deleted in a new standard, but not described as such in the standard,
which is why we do not have GFC_STD_F2023_DEL.  As -std=gnu should not
apply this restriction, I came up with the solution in the patch.
While playing, I hit a gcc_unreachable in notify_std_msg due to a
missing case, also fixed.

Interestingly, the standard now has a recommendation:

16.9.202 SYSTEM_CLOCK

It it recommended that all references to SYSTEM_CLOCK use integer
arguments with a decimal exponent range of at least 18. ...

In case the user chooses integer(4), shall we emit a warning
e.g. under -pedantic, or some other flag?  This is not done
in the patch, but could be added.

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

Thanks,
Harald

From 44814d9436b2e0be14b76b137602e40f3fdaf805 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Sat, 18 Nov 2023 22:51:35 +0100
Subject: [PATCH] Fortran: restrictions on integer arguments to SYSTEM_CLOCK
 [PR112609]

Fortran 2023 added restrictions on integer arguments to SYSTEM_CLOCK to
have a decimal exponent range at least as large as a default integer,
and that all integer arguments have the same kind type parameter.

gcc/fortran/ChangeLog:

	PR fortran/112609
	* check.cc (gfc_check_system_clock): Add checks on integer arguments
	to SYSTEM_CLOCK specific to F2023.
	* error.cc (notify_std_msg): Adjust to handle new features added
	in F2023.

gcc/testsuite/ChangeLog:

	PR fortran/112609
	* gfortran.dg/system_clock_4.f90: New test.
---
 gcc/fortran/check.cc | 57 
 gcc/fortran/error.cc |  4 +-
 gcc/testsuite/gfortran.dg/system_clock_4.f90 | 24 +
 3 files changed, 84 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/system_clock_4.f90

diff --git a/gcc/fortran/check.cc b/gcc/fortran/check.cc
index 6c45e6542f0..8c2534ae1c9 100644
--- a/gcc/fortran/check.cc
+++ b/gcc/fortran/check.cc
@@ -6774,6 +6774,10 @@ bool
 gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			gfc_expr *count_max)
 {
+  int first_int_kind = -1;
+  bool f2023 = ((gfc_option.allow_std & GFC_STD_F2023) != 0
+		&& (gfc_option.allow_std & GFC_STD_GNU) == 0);
+
   if (count != NULL)
 {
   if (!scalar_check (count, 0))
@@ -6788,8 +6792,18 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			  &count->where))
 	return false;

+  if (f2023 && count->ts.kind < gfc_default_integer_kind)
+	{
+	  gfc_error ("Fortran 2023: COUNT argument to SYSTEM_CLOCK "
+		 "at %L must have kind of at least default integer",
+		 &count->where);
+	  return false;
+	}
+
   if (!variable_check (count, 0, false))
 	return false;
+
+  first_int_kind = count->ts.kind;
 }

   if (count_rate != NULL)
@@ -6816,6 +6830,17 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
   "SYSTEM_CLOCK at %L has non-default kind",
   &count_rate->where))
 	return false;
+
+	  if (f2023 && count_rate->ts.kind < gfc_default_integer_kind)
+	{
+	  gfc_error ("Fortran 2023: COUNT_RATE argument to SYSTEM_CLOCK "
+			 "at %L must have kind of at least default integer",
+			 &count_rate->where);
+	  return false;
+	}
+
+	  if (first_int_kind < 0)
+	first_int_kind = count_rate->ts.kind;
 	}

 }
@@ -6836,6 +6861,38 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,

   if (!variable_check (count_max, 2, false))
 	return false;
+
+  if (f2023 && count_max->ts.kind < gfc_default_integer_kind)
+	{
+	  gfc_error ("Fortran 2023: COUNT_MAX argument to SYSTEM_CLOCK "
+		 "at %L must have kind of at least default integer",
+		 &count_max->where);
+	  return false;
+	}
+
+  if (first_int_kind < 0)
+	first_int_kind = count_max->ts.kind;
+}
+
+  if (f2023 && first_int_kind > 0)
+{
+  if (count_rate
+	  && count_rate->ts.type == BT_INTEGER
+	  && count_rate->ts.kind != first_int_kind)
+	{
+	  gfc_error ("Fortran 2023: all integer arguments to SYSTEM_CLOCK "
+		 "at %L must have the same kind",
+		 &count_rate->where);
+	  return false;
+	}
+
+  if (count_max && count_max->ts.kind != first_int_kind)
+	{
+	  gfc_error ("Fortran 2023: all integer arguments to SYSTEM_CLOCK "
+		 "at %L must have the same kind",
+		 &count_max->where);
+	  return false;
+	}
 }

   return true;
diff --git a/gcc/fortran/error.cc b/gcc/fortran/error.cc
index 2ac51e95e4d..b8b36c0cd7c 100644
--- a/gcc/fortran/error.cc
+++ b/gcc/fortran/error.cc
@@ -980,7 +980,9 @@ char c

[PATCH, v2] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-19 Thread Harald Anlauf

Hi Steve,

On 11/19/23 01:04, Steve Kargl wrote:

On Sat, Nov 18, 2023 at 11:12:55PM +0100, Harald Anlauf wrote:

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



Not in its current form.


  {
+  int first_int_kind = -1;
+  bool f2023 = ((gfc_option.allow_std & GFC_STD_F2023) != 0
+   && (gfc_option.allow_std & GFC_STD_GNU) == 0);
+


If you use the gfc_notify_std(), then you should not need the
above check on GFC_STD_GNU as it should include GFC_STD_F2023.


this is actually the question (and problem).  For all new features,
-std=gnu shall include everything allowed by -std=f2023.

Here we have the problem that the testcase is valid F2018 and is
silently accepted by gfortran-13 for -std=gnu and -std=f2018.

I prefer to keep it that way also for gfortran-14, and apply the
new restrictions only for -std=f2023.  Do we agree on this?

Now that should happen for -std=gnu -pedantic (-w)?

I have thought some more and came up with the revised attached
patch, which still has the above condition.  It now marks the
diagnostics as GNU extensions beyond F2023 for -std=f2023.

The mask f2023 in the above form suppresses new warnings even
for -pedantic; one would normally use -w to suppress them.

Now if you remove the second part of the condition, we will
regress on testcases system_clock_1.f90 and system_clock_3.f90
because they would emit GNU extension warnings because the
testsuite runs with -pedantic.

The options I see:

- use patch-V1 (although diagnostics are better in V2),

- use patch-V2,

- use patch-V2, but enable -pedantic warnings for previously
  valid code, and adjust the failing testcases

- ???


Elsewhere in the FE, gfortran uses gfc_notify_std() to enforce
requirements of a Fortran standard.  The above would be

   if (count->ts.kind < gfc_default_integer_kind
   && gfc_notify_std (GFC_STD_F2023, "COUNT argument to SYSTEM_CLOCK "
  "at %L must have kind of at least default 
integer",
  &count->where))


I tried this first, and it did not do the job.

The logic in gfc_notify_std is:

  estd = std & ~gfc_option.allow_std;  /* Standard to error about.  */
  error = (estd != 0);
  if (error)
msg = notify_std_msg (estd);
...

So for -std=f2023 we get estd=0, error=false, and *NO* error.
For -std=f2018 we get error=true and an error message.
This is the opposite of what is needed.

Can you please try yourself?


Note, gfc_notify_std() should add the 'Fortran 2023: ' string,
if not, that should be fixed.


This I did fix.


Of course, I seldom provide patches if others don't have a comment
then do as you like.


Thanks for your feedback!

Harald

From 2a85dc469696c85524459380ce11faa20e558680 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Sun, 19 Nov 2023 21:14:37 +0100
Subject: [PATCH] Fortran: restrictions on integer arguments to SYSTEM_CLOCK
 [PR112609]

Fortran 2023 added restrictions on integer arguments to SYSTEM_CLOCK to
have a decimal exponent range at least as large as a default integer,
and that all integer arguments have the same kind type parameter.

gcc/fortran/ChangeLog:

	PR fortran/112609
	* check.cc (gfc_check_system_clock): Add checks on integer arguments
	to SYSTEM_CLOCK specific to F2023.
	* error.cc (notify_std_msg): Adjust to handle new features added
	in F2023.

gcc/testsuite/ChangeLog:

	PR fortran/112609
	* gfortran.dg/system_clock_4.f90: New test.
---
 gcc/fortran/check.cc | 52 
 gcc/fortran/error.cc |  4 +-
 gcc/testsuite/gfortran.dg/system_clock_4.f90 | 24 +
 3 files changed, 79 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/system_clock_4.f90

diff --git a/gcc/fortran/check.cc b/gcc/fortran/check.cc
index 6c45e6542f0..faaea853bc4 100644
--- a/gcc/fortran/check.cc
+++ b/gcc/fortran/check.cc
@@ -6774,6 +6774,10 @@ bool
 gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			gfc_expr *count_max)
 {
+  int first_int_kind = -1;
+  bool f2023 = ((gfc_option.allow_std & GFC_STD_F2023) != 0
+		&& (gfc_option.allow_std & GFC_STD_GNU) == 0);
+
   if (count != NULL)
 {
   if (!scalar_check (count, 0))
@@ -6788,8 +6792,17 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			  &count->where))
 	return false;
 
+  if (f2023 && count->ts.kind < gfc_default_integer_kind
+	  && !gfc_notify_std (GFC_STD_GNU, "Fortran 2023 requires "
+			  "COUNT argument to SYSTEM_CLOCK at %L "
+			  "to have a kind of at least default integer",
+			  &count->where))
+	return false;
+
   if (!variable_check (count, 0, false))
 	return false;
+
+  first_int_kind = count->ts.kind;
 }
 
   if (count_rate != NULL)
@@ -6816,6 +6829,16 @@ gfc_check_system_clock (gfc_expr *coun

[PATCH, v3] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-21 Thread Harald Anlauf

Hi Mikael, Steve,

On 11/21/23 12:33, Mikael Morin wrote:

Harald, you mentioned the lack of GFC_STD_F2023_DEL feature group in
your first message, but I don't quite understand why you didn't add one.
  It seems to me the most natural way to do this.


thanks for insisting on this variant.

In my first attack at this problem, I overlooked one place in
libgfortran.h, which I now was able to find and adjust.
Now everything falls into place.


I suggest we emit a warning by default, error with -std=f2023 (I agree
with Steve that we should push towards strict f2023 conformance), and no
diagnostic with -std=gnu or -std=f2018 or lower.


As the majority agrees on this, I accept it.  The attached patch
now does this and fixes the testcases accordingly.


It seems that the solution is to fix the code in the testsuite.


Agreed, these seem to explicitly test mismatching kinds, so add an
option to prevent error.


Done.

I also fixed a few issues in the documentation in gfortran.texi .

As I currently cannot build a full compiler (see PR112643),
patch V3 is not properly regtested yet, but appears to give
results as discussed.

Comments?


Mikael


Thanks,
Harald


diff --git a/gcc/fortran/check.cc b/gcc/fortran/check.cc
index 6c45e6542f0..e5cf6a495b5 100644
--- a/gcc/fortran/check.cc
+++ b/gcc/fortran/check.cc
@@ -4357,6 +4357,9 @@ gfc_check_null (gfc_expr *mold)
   if (mold == NULL)
 return true;
 
+  if (mold->expr_type == EXPR_NULL)
+return true;
+
   if (!variable_check (mold, 0, true))
 return false;
 
@@ -5189,7 +5192,7 @@ is_c_interoperable (gfc_expr *expr, const char **msg, bool c_loc, bool c_f_ptr)
 {
   *msg = NULL;
 
-  if (expr->expr_type == EXPR_NULL)
+  if (expr->expr_type == EXPR_NULL && expr->ts.type == BT_UNKNOWN)
 {
   *msg = "NULL() is not interoperable";
   return false;
diff --git a/gcc/fortran/interface.cc b/gcc/fortran/interface.cc
index fc4fe662eab..641edf9d059 100644
--- a/gcc/fortran/interface.cc
+++ b/gcc/fortran/interface.cc
@@ -2387,6 +2387,8 @@ compare_parameter (gfc_symbol *formal, gfc_expr *actual,
   gfc_component *ppc;
   bool codimension = false;
   gfc_array_spec *formal_as;
+  bool pointer_arg, allocatable_arg;
+  bool pre2018 = ((gfc_option.allow_std & GFC_STD_F2018) == 0);
 
   /* If the formal arg has type BT_VOID, it's to one of the iso_c_binding
  procs c_f_pointer or c_f_procpointer, and we need to accept most
@@ -2564,13 +2566,20 @@ compare_parameter (gfc_symbol *formal, gfc_expr *actual,
 	}
 }
 
+  pointer_arg = gfc_expr_attr (actual).pointer;
+  allocatable_arg = gfc_expr_attr (actual).allocatable;
+
   /* F08: 12.5.2.5 Allocatable and pointer dummy variables.  However, this
  is necessary also for F03, so retain error for both.
+ F2018:15.5.2.5 relaxes this constraint to same attributes.
  NOTE: Other type/kind errors pre-empt this error.  Since they are F03
  compatible, no attempt has been made to channel to this one.  */
   if (UNLIMITED_POLY (formal) && !UNLIMITED_POLY (actual)
   && (CLASS_DATA (formal)->attr.allocatable
-	  ||CLASS_DATA (formal)->attr.class_pointer))
+	  || CLASS_DATA (formal)->attr.class_pointer)
+  && (pre2018
+	  || (allocatable_arg && CLASS_DATA (formal)->attr.allocatable)
+	  || (pointer_arg && CLASS_DATA (formal)->attr.class_pointer)))
 {
   if (where)
 	gfc_error ("Actual argument to %qs at %L must be unlimited "
@@ -2710,7 +2719,8 @@ compare_parameter (gfc_symbol *formal, gfc_expr *actual,
   rank_check = where != NULL && !is_elemental && formal_as
 && (formal_as->type == AS_ASSUMED_SHAPE
 	|| formal_as->type == AS_DEFERRED)
-&& actual->expr_type != EXPR_NULL;
+&& !(actual->expr_type == EXPR_NULL
+	 && actual->ts.type == BT_UNKNOWN);
 
   /* Skip rank checks for NO_ARG_CHECK.  */
   if (formal->attr.ext_attr & (1 << EXT_ATTR_NO_ARG_CHECK))
@@ -3184,8 +3194,10 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
   gfc_array_ref *actual_arr_ref;
   gfc_array_spec *fas, *aas;
   bool pointer_dummy, pointer_arg, allocatable_arg;
+  bool procptr_dummy, optional_dummy, allocatable_dummy;
 
   bool ok = true;
+  bool pre2018 = ((gfc_option.allow_std & GFC_STD_F2018) == 0);
 
   actual = *ap;
 
@@ -3296,15 +3308,66 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
 	  && a->expr->ts.type != BT_ASSUMED)
 	gfc_find_vtab (&a->expr->ts);
 
+  /* Checks for NULL() actual arguments without MOLD.  */
+  if (a->expr->expr_type == EXPR_NULL && a->expr->ts.type == BT_UNKNOWN)
+	{
+	  /* Interp J3/22-146:
+	 "If the context of the reference to NULL is an 
+	 corresponding to an  dummy argument, MOLD shall be
+	 present."  */
+	  fas = (f->sym->ts.type == BT_CLASS && CLASS_DATA (f->sym)
+		 ? CLASS_DATA (f->sym)->as
+		 : f->sym->as);
+	  if (fas && fas->type == AS_ASSUMED_RANK)
+	{
+	  gfc_error ("Intrinsic % without % argument "
+			 "at %L passed to assumed-rank dummy %qs",
+			 &a->expr->

Re: [PATCH, v3] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-21 Thread Harald Anlauf

Uhh, it happened again.  Attached a wrong patch.
Only looked at the -v3 ...  My bad.

Sorry!

Harald


On 11/21/23 22:54, Harald Anlauf wrote:

Hi Mikael, Steve,

On 11/21/23 12:33, Mikael Morin wrote:

Harald, you mentioned the lack of GFC_STD_F2023_DEL feature group in
your first message, but I don't quite understand why you didn't add one.
  It seems to me the most natural way to do this.


thanks for insisting on this variant.

In my first attack at this problem, I overlooked one place in
libgfortran.h, which I now was able to find and adjust.
Now everything falls into place.


I suggest we emit a warning by default, error with -std=f2023 (I agree
with Steve that we should push towards strict f2023 conformance), and no
diagnostic with -std=gnu or -std=f2018 or lower.


As the majority agrees on this, I accept it.  The attached patch
now does this and fixes the testcases accordingly.


It seems that the solution is to fix the code in the testsuite.


Agreed, these seem to explicitly test mismatching kinds, so add an
option to prevent error.


Done.

I also fixed a few issues in the documentation in gfortran.texi .

As I currently cannot build a full compiler (see PR112643),
patch V3 is not properly regtested yet, but appears to give
results as discussed.

Comments?


Mikael


Thanks,
Harald


From 8fbffe1bd1faaff456abf6730ac2e2b3c370bc72 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 21 Nov 2023 22:29:19 +0100
Subject: [PATCH] Fortran: restrictions on integer arguments to SYSTEM_CLOCK
 [PR112609]

Fortran 2023 added restrictions on integer arguments to SYSTEM_CLOCK to
have a decimal exponent range at least as large as a default integer,
and that all integer arguments have the same kind type parameter.

gcc/fortran/ChangeLog:

	PR fortran/112609
	* check.cc (gfc_check_system_clock): Add checks on integer arguments
	to SYSTEM_CLOCK specific to F2023.
	* error.cc (notify_std_msg): Adjust to handle new features added
	in F2023.
	* gfortran.texi (_gfortran_set_options): Document GFC_STD_F2023_DEL,
	remove obsolete option GFC_STD_F2008_TS and fix enumeration values.
	* libgfortran.h (GFC_STD_F2023_DEL): Add and use in GFC_STD_OPT_F23.
	* options.cc (set_default_std_flags): Add GFC_STD_F2023_DEL.

gcc/testsuite/ChangeLog:

	PR fortran/112609
	* gfortran.dg/system_clock_1.f90: Add option -std=f2003.
	* gfortran.dg/system_clock_3.f08: Add option -std=f2008.
	* gfortran.dg/system_clock_4.f90: New test.
---
 gcc/fortran/check.cc | 50 
 gcc/fortran/error.cc |  6 ++-
 gcc/fortran/gfortran.texi| 10 ++--
 gcc/fortran/libgfortran.h|  8 ++--
 gcc/fortran/options.cc   |  6 ++-
 gcc/testsuite/gfortran.dg/system_clock_1.f90 |  1 +
 gcc/testsuite/gfortran.dg/system_clock_3.f08 |  1 +
 gcc/testsuite/gfortran.dg/system_clock_4.f90 | 24 ++
 8 files changed, 95 insertions(+), 11 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/system_clock_4.f90

diff --git a/gcc/fortran/check.cc b/gcc/fortran/check.cc
index 6c45e6542f0..3b1a0f9f4f4 100644
--- a/gcc/fortran/check.cc
+++ b/gcc/fortran/check.cc
@@ -6774,6 +6774,8 @@ bool
 gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			gfc_expr *count_max)
 {
+  int first_int_kind = -1;
+
   if (count != NULL)
 {
   if (!scalar_check (count, 0))
@@ -6788,8 +6790,17 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 			  &count->where))
 	return false;
 
+  if (count->ts.kind < gfc_default_integer_kind
+	  && !gfc_notify_std (GFC_STD_F2023_DEL,
+			  "COUNT argument to SYSTEM_CLOCK at %L "
+			  "with kind smaller than default integer",
+			  &count->where))
+	return false;
+
   if (!variable_check (count, 0, false))
 	return false;
+
+  first_int_kind = count->ts.kind;
 }
 
   if (count_rate != NULL)
@@ -6816,6 +6827,16 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
   "SYSTEM_CLOCK at %L has non-default kind",
   &count_rate->where))
 	return false;
+
+	  if (count_rate->ts.kind < gfc_default_integer_kind
+	  && !gfc_notify_std (GFC_STD_F2023_DEL,
+  "COUNT_RATE argument to SYSTEM_CLOCK at %L "
+  "with kind smaller than default integer",
+  &count_rate->where))
+	return false;
+
+	  if (first_int_kind < 0)
+	first_int_kind = count_rate->ts.kind;
 	}
 
 }
@@ -6836,6 +6857,35 @@ gfc_check_system_clock (gfc_expr *count, gfc_expr *count_rate,
 
   if (!variable_check (count_max, 2, false))
 	return false;
+
+  if (count_max->ts.kind < gfc_default_integer_kind
+	  && !gfc_notify_std (GFC_STD_F2023_DEL,
+			  "COUNT_MAX argument to SYSTEM_CLOCK at %L "
+			  "with kind smaller than default integer",
+			  &count_max->where))
+	re

Re: [PATCH, v3] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-22 Thread Harald Anlauf

Hi Steve,

On 11/22/23 19:03, Steve Kargl wrote:

On Wed, Nov 22, 2023 at 10:36:00AM +0100, Mikael Morin wrote:


OK with this fixed (and the previous comments as you wish), if Steve has no
more comments.



No further comments.  Thanks for your patients, Harald.

As side note, I found John Reid's "What's new" document
where it is noted that there are no new obsolescent or
delete features.

https://wg5-fortran.org/N2201-N2250/N2212.pdf



this is good to know.

There is an older version (still referring to F202x) on the wiki:

https://gcc.gnu.org/wiki/GFortranStandards

It would be great if someone with editing permission could update
the link and point to the above.

Thanks,
Harald



[PATCH, testsuite, fortran] fix invalid testcases (missing MOLD argument to NULL)

2023-11-22 Thread Harald Anlauf
Dear all,

testcases assumed_rank_8.f90 and assumed_rank_10.f90 are invalid:
NULL() is passed without MOLD to an assumed-rank dummy argument.

This is detected by NAG, but not yet by gfortran (see pr104819).
gfortran even ignores the MOLD argument; the dump-tree is identical
if MOLD is there or not.

Now these testcases are { dg-do run }.  Therefore I would like to
fix these testcases, independent of the work on fixing pr104819.

Comments?

Thanks,
Harald

From cbb0c61f9d6f06667666a33da6e6ce3213a92248 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Wed, 22 Nov 2023 21:45:46 +0100
Subject: [PATCH] testsuite: fortran: fix invalid testcases (missing MOLD
 argument to NULL)

The Fortran standard requires that NULL() passed to an assumed-rank
dummy argument has a MOLD argument.

gcc/testsuite/ChangeLog:

	PR fortran/104819
	* gfortran.dg/assumed_rank_10.f90: Add MOLD argument to NULL().
	* gfortran.dg/assumed_rank_8.f90: Likewise.
---
 gcc/testsuite/gfortran.dg/assumed_rank_10.f90 | 6 +++---
 gcc/testsuite/gfortran.dg/assumed_rank_8.f90  | 4 ++--
 2 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/gcc/testsuite/gfortran.dg/assumed_rank_10.f90 b/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
index 6a3cc94483e..f22d43ab955 100644
--- a/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
+++ b/gcc/testsuite/gfortran.dg/assumed_rank_10.f90
@@ -50,9 +50,9 @@ program test

  is_present = .false.

- call fpa(null(), null()) ! No copy back
- call fpi(null(), null()) ! No copy back
- call fno(null(), null()) ! No copy back
+ call fpa(null(iip), null(jjp)) ! No copy back
+ call fpi(null(iip), null(jjp)) ! No copy back
+ call fno(null(iip), null(jjp)) ! No copy back

  call fno() ! No copy back

diff --git a/gcc/testsuite/gfortran.dg/assumed_rank_8.f90 b/gcc/testsuite/gfortran.dg/assumed_rank_8.f90
index 5873296a7a5..34ff42c0be2 100644
--- a/gcc/testsuite/gfortran.dg/assumed_rank_8.f90
+++ b/gcc/testsuite/gfortran.dg/assumed_rank_8.f90
@@ -22,13 +22,13 @@ program main
   call f (ii)
   call f (489)
   call f ()
-  call f (null())
+  call f (null(kk))
   call f (kk)
   if (j /= 2) STOP 1

   j = 0
   nullify (ll)
-  call g (null())
+  call g (null(ll))
   call g (ll)
   call g (ii)
   if (j /= 1) STOP 2
--
2.35.3



[PATCH, v4] Fortran: restrictions on integer arguments to SYSTEM_CLOCK [PR112609]

2023-11-22 Thread Harald Anlauf

Hi Mikael!

On 11/22/23 10:36, Mikael Morin wrote:

(...)


diff --git a/gcc/fortran/error.cc b/gcc/fortran/error.cc
index 2ac51e95e4d..be715b50469 100644
--- a/gcc/fortran/error.cc
+++ b/gcc/fortran/error.cc
@@ -980,7 +980,11 @@ char const*
 notify_std_msg(int std)
 {

-  if (std & GFC_STD_F2018_DEL)
+  if (std & GFC_STD_F2023_DEL)
+    return _("Fortran 2023 deleted feature:");


As there are officially no deleted feature in f2023, maybe use a 
slightly different wording?  Say "Not allowed in fortran 2023" or 
"forbidden in Fortran 2023" or similar?



+  else if (std & GFC_STD_F2023)
+    return _("Fortran 2023:");
+  else if (std & GFC_STD_F2018_DEL)
 return _("Fortran 2018 deleted feature:");
   else if (std & GFC_STD_F2018_OBS)
 return _("Fortran 2018 obsolescent feature:");


I skimmed over existing error messages, and since "forbidden" did
not show up and since "Not allowed" exists but not at the beginning
of a message, I found that

"Prohibited in Fortran 2023"

appeared to be a good alternative.

Not being a native speaker, I hope that someone speaks up if this
is not appropriate.  And since I do not explicitly verify that part
in the testcase, it can be changed.


diff --git a/gcc/fortran/libgfortran.h b/gcc/fortran/libgfortran.h
index bdddb317ab0..af7a170c2b1 100644
--- a/gcc/fortran/libgfortran.h
+++ b/gcc/fortran/libgfortran.h
@@ -19,9 +19,10 @@ along with GCC; see the file COPYING3.  If not see


 /* Flags to specify which standard/extension contains a feature.
-   Note that no features were obsoleted nor deleted in F2003 nor in 
F2023.

+   Note that no features were obsoleted nor deleted in F2003.


I think we can add a comment that F2023 has no deleted feature, but some 
more stringent restrictions in f2023 forbid some previously valid code.



    Please remember to keep those definitions in sync with
    gfortran.texi.  */
+#define GFC_STD_F2023_DEL    (1<<13)    /* Deleted in F2023.  */
 #define GFC_STD_F2023    (1<<12)    /* New in F2023.  */
 #define GFC_STD_F2018_DEL    (1<<11)    /* Deleted in F2018.  */
 #define GFC_STD_F2018_OBS    (1<<10)    /* Obsolescent in F2018.  */
@@ -41,12 +42,13 @@ along with GCC; see the file COPYING3.  If not see
  * are allowed with a certain -std option.  */
 #define GFC_STD_OPT_F95    (GFC_STD_F77 | GFC_STD_F95 | 
GFC_STD_F95_OBS  \

 | GFC_STD_F2008_OBS | GFC_STD_F2018_OBS \
-    | GFC_STD_F2018_DEL)
+    | GFC_STD_F2018_DEL | GFC_STD_F2023_DEL)
 #define GFC_STD_OPT_F03    (GFC_STD_OPT_F95 | GFC_STD_F2003)
 #define GFC_STD_OPT_F08    (GFC_STD_OPT_F03 | GFC_STD_F2008)
 #define GFC_STD_OPT_F18    ((GFC_STD_OPT_F08 | GFC_STD_F2018) \
 & (~GFC_STD_F2018_DEL))
F03, F08 and F18 should have GFC_STD_F2023_DEL (and also F03 and F08 
should have GFC_STD_F2018_DEL).


Well, these macros do an incremental bitwise-or, so the bit representing
GFC_STD_F2023_DEL is included everywhere.  I also ran the testcases with
different -std= options to check.

OK with this fixed (and the previous comments as you wish), if Steve has 
no more comments.


Thanks for the patch.




If there are no further comments, I will commit once I am able to
fully build again with --disable-bootstrap and -march=native ...

Thanks,
Harald

From 56386f4f332cf8970a424ba67678335fa6186e4c Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Wed, 22 Nov 2023 20:57:59 +0100
Subject: [PATCH] Fortran: restrictions on integer arguments to SYSTEM_CLOCK
 [PR112609]

Fortran 2023 added restrictions on integer arguments to SYSTEM_CLOCK to
have a decimal exponent range at least as large as a default integer,
and that all integer arguments have the same kind type parameter.

gcc/fortran/ChangeLog:

	PR fortran/112609
	* check.cc (gfc_check_system_clock): Add checks on integer arguments
	to SYSTEM_CLOCK specific to F2023.
	* error.cc (notify_std_msg): Adjust to handle new features added
	in F2023.
	* gfortran.texi (_gfortran_set_options): Document GFC_STD_F2023_DEL,
	remove obsolete option GFC_STD_F2008_TS and fix enumeration values.
	* libgfortran.h (GFC_STD_F2023_DEL): Add and use in GFC_STD_OPT_F23.
	* options.cc (set_default_std_flags): Add GFC_STD_F2023_DEL.

gcc/testsuite/ChangeLog:

	PR fortran/112609
	* gfortran.dg/system_clock_1.f90: Add option -std=f2003.
	* gfortran.dg/system_clock_3.f08: Add option -std=f2008.
	* gfortran.dg/system_clock_4.f90: New test.
---
 gcc/fortran/check.cc | 50 
 gcc/fortran/error.cc |  6 ++-
 gcc/fortran/gfortran.texi| 10 ++--
 gcc/fortran/libgfortran.h|  7 ++-
 gcc/fortran/options.cc   |  6 ++-
 gcc/testsuite/gfortran.dg/system_clock_1.f90 |  1 +
 gcc/testsuite/gfortran.dg/system_clock_3.f08 |  1 +
 gcc/testsuite/gfortr

[PATCH] Fortran: avoid obsolescence warning for COMMON with submodule [PR111880]

2023-11-23 Thread Harald Anlauf
Dear all,

the PR is about a redundant obsolescence warning for COMMON when
a symbols appears in the scope of a submodule.  As we did not warn
for use-associated symbols, it seemed natural to extend this to
symbols that are used in a submodule.  Or am I missing anything?

Regtests cleanly on x86_64-pc-linux-gnu.  OK for mainline?

The PR is marked as a regression (the warning appeared in gcc-9).
It looks simple enough for backporting, or does anybody see any
risk here?

Thanks,
Harald

From a962ab0417f5ff2efd51e710ae370d9f4a4b9f1a Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Thu, 23 Nov 2023 22:48:38 +0100
Subject: [PATCH] Fortran: avoid obsolescence warning for COMMON with submodule
 [PR111880]

gcc/fortran/ChangeLog:

	PR fortran/111880
	* resolve.cc (resolve_common_vars): Do not call gfc_add_in_common
	for symbols that are USE associated or used in a submodule.

gcc/testsuite/ChangeLog:

	PR fortran/111880
	* gfortran.dg/pr111880.f90: New test.
---
 gcc/fortran/resolve.cc |  4 ++--
 gcc/testsuite/gfortran.dg/pr111880.f90 | 22 ++
 2 files changed, 24 insertions(+), 2 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/pr111880.f90

diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc
index 81a14653a04..166b702cd9a 100644
--- a/gcc/fortran/resolve.cc
+++ b/gcc/fortran/resolve.cc
@@ -986,8 +986,8 @@ resolve_common_vars (gfc_common_head *common_block, bool named_common)

   /* gfc_add_in_common may have been called before, but the reported errors
 	 have been ignored to continue parsing.
-	 We do the checks again here.  */
-  if (!csym->attr.use_assoc)
+	 We do the checks again here, unless the symbol is USE associated.  */
+  if (!csym->attr.use_assoc && !csym->attr.used_in_submodule)
 	{
 	  gfc_add_in_common (&csym->attr, csym->name, &common_block->where);
 	  gfc_notify_std (GFC_STD_F2018_OBS, "COMMON block at %L",
diff --git a/gcc/testsuite/gfortran.dg/pr111880.f90 b/gcc/testsuite/gfortran.dg/pr111880.f90
new file mode 100644
index 000..c0cd98a93d4
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr111880.f90
@@ -0,0 +1,22 @@
+! { dg-do compile }
+! { dg-options "-std=f2018" }
+! PR fortran/111880 - redundant warning of obsolescent COMMON with submodule
+
+module third_party_module
+  integer :: some_param
+  common /not_my_code/ some_param   ! { dg-warning "COMMON block" }
+end module third_party_module
+
+module foo
+  use third_party_module
+  interface
+module subroutine bar()
+end subroutine bar
+  end interface
+end module foo
+
+submodule (foo) foo_submod  ! We do not need a warning here!
+contains
+  module procedure bar
+  end procedure bar
+end submodule foo_submod
--
2.35.3



[PATCH] Fortran: deferred-length character optional dummy arguments [PR93762,PR100651]

2023-11-27 Thread Harald Anlauf
Dear all,

the attached patch fixes the passing of deferred-length character
to optional dummy arguments: the character length shall be passed
by reference, not by value.

Original analysis of the issue by Steve in PR93762, independently
done by FX in PR100651.  The patch fixes both PRs.

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

As the fix is local and affects only deferred-length character,
would it be ok to backport to 13-branch?

Thanks,
Harald

From 8ce1c8e7d0390361a1507000b7abbf6509b2fee9 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Mon, 27 Nov 2023 20:19:11 +0100
Subject: [PATCH] Fortran: deferred-length character optional dummy arguments
 [PR93762,PR100651]

gcc/fortran/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* trans-expr.cc (gfc_conv_missing_dummy): The character length for
	deferred-length dummy arguments is passed by reference, so that its
	value can be returned.  Adjust handling for optional dummies.

gcc/testsuite/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* gfortran.dg/optional_deferred_char_1.f90: New test.
---
 gcc/fortran/trans-expr.cc |  22 +++-
 .../gfortran.dg/optional_deferred_char_1.f90  | 100 ++
 2 files changed, 118 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 50c4604a025..e992f60d8bb 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -2116,10 +2116,24 @@ gfc_conv_missing_dummy (gfc_se * se, gfc_expr * arg, gfc_typespec ts, int kind)

   if (ts.type == BT_CHARACTER)
 {
-  tmp = build_int_cst (gfc_charlen_type_node, 0);
-  tmp = fold_build3_loc (input_location, COND_EXPR, gfc_charlen_type_node,
-			 present, se->string_length, tmp);
-  tmp = gfc_evaluate_now (tmp, &se->pre);
+  /* Handle deferred-length dummies that pass the character length by
+	 reference so that the value can be returned.  */
+  if (ts.deferred && INDIRECT_REF_P (se->string_length))
+	{
+	  tmp = gfc_build_addr_expr (NULL_TREE, se->string_length);
+	  tmp = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp),
+ present, tmp, null_pointer_node);
+	  tmp = gfc_evaluate_now (tmp, &se->pre);
+	  tmp = build_fold_indirect_ref_loc (input_location, tmp);
+	}
+  else
+	{
+	  tmp = build_int_cst (gfc_charlen_type_node, 0);
+	  tmp = fold_build3_loc (input_location, COND_EXPR,
+ gfc_charlen_type_node,
+ present, se->string_length, tmp);
+	  tmp = gfc_evaluate_now (tmp, &se->pre);
+	}
   se->string_length = tmp;
 }
   return;
diff --git a/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90 b/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90
new file mode 100644
index 000..d399dd11ca2
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90
@@ -0,0 +1,100 @@
+! { dg-do run }
+! PR fortran/93762
+! PR fortran/100651 - deferred-length character as optional dummy argument
+
+program main
+  implicit none
+  character(:), allocatable :: err_msg, msg3(:)
+  character(:), pointer :: err_msg2 => NULL()
+
+  ! Subroutines with optional arguments
+  call to_int ()
+  call to_int_p ()
+  call test_rank1 ()
+  call assert_code ()
+  call assert_p ()
+  call assert_rank1 ()
+
+  ! Test passing of optional arguments
+  call to_int (err_msg)
+  if (.not. allocated (err_msg)) stop 1
+  if (len (err_msg) /= 7)stop 2
+  if (err_msg(1:7) /= "foo bar") stop 3
+
+  call to_int2 (err_msg)
+  if (.not. allocated (err_msg)) stop 4
+  if (len (err_msg) /= 7)stop 5
+  if (err_msg(1:7) /= "foo bar") stop 6
+  deallocate (err_msg)
+
+  call to_int_p (err_msg2)
+  if (.not. associated (err_msg2)) stop 11
+  if (len (err_msg2) /= 8) stop 12
+  if (err_msg2(1:8) /= "poo bla ") stop 13
+  deallocate (err_msg2)
+
+  call to_int2_p (err_msg2)
+  if (.not. associated (err_msg2)) stop 14
+  if (len (err_msg2) /= 8) stop 15
+  if (err_msg2(1:8) /= "poo bla ") stop 16
+  deallocate (err_msg2)
+
+  call test_rank1 (msg3)
+  if (.not. allocated (msg3)) stop 21
+  if (len (msg3) /= 2)stop 22
+  if (size (msg3) /= 42)  stop 23
+  if (any (msg3 /= "ok")) stop 24
+  deallocate (msg3)
+
+contains
+
+  ! Deferred-length character, allocatable:
+  subroutine assert_code (err_msg0)
+character(:), optional, allocatable :: err_msg0
+if (present (err_msg0)) err_msg0 = 'foo bar'
+  end
+  ! Test: optional argument
+  subroutine to_int (err_msg1)
+character(:), optional, allocatable :: err_msg1
+call assert_code (err_msg1)
+  end
+  ! Control: non-optional argument
+  subroutine to_int2 (err_msg2)
+character(:), allocatable :: err_msg2
+call assert_code (err_msg2)
+  end
+
+  ! Rank-1:
+  subroutine assert_rank1 (msg)
+character(:), optional, allocatable, intent(out) :: msg(:

Re: [PATCH] Fortran: deferred-length character optional dummy arguments [PR93762,PR100651]

2023-11-28 Thread Harald Anlauf

Hi FX,

On 11/28/23 18:07, FX Coudert wrote:

Hi Harald,

The patch looks OK to me. Probably wait a bit for another opinion, since I’m 
not that active and I may have missed something.

Thanks,
FX


thanks for having a look.

In the meantime I got an automated mail from the Linaro testers.
According to it there is a runtime failure of the testcase on
aarch64.  I couldn't see any useful traceback or else.

I tried the testcase on x86 with different options and found
an unexpected result only with -fsanitize=undefined and only
for the case of a rank-1 dummy when there is no actual argument
and the passed to another subroutine.  (valgrind is happy.)

Reduced reproducer:

! this fails with -fsanitize=undefined
program main
  call test_rank1 ()
contains
  subroutine test_rank1 (msg1)
character(:), optional, allocatable :: msg1(:)
if (present (msg1)) stop 77
call assert_rank1 ()! <- no problem here
call assert_rank1 (msg1)! <- problematic code path
  end

  subroutine assert_rank1 (msg2)
character(:), optional, allocatable :: msg2(:)
if (present (msg2)) stop 99 ! <- no problem if commented
  end
end


As far as I can tell, this could be a pre-existing (latent)
issue.  By looking at the tree-dump, the only thing that
appears fishy has been there before.  But then I am only
guessing that this is the problem observed on aarch64.

I have disabled the related call in the testcase of the
attached revised version.  As I do not see anything else,
I wonder if one could proceed with the current version
but open a PR for the reduced case above, unless someone
can pinpoint the place that is responsible for the above
failure.  (Is it the caller, or rather the function entry
code in the callee?)

Cheers,
Harald

From 63879942b491e23eefc6da4d80c5492434e42ec8 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Tue, 28 Nov 2023 20:19:14 +0100
Subject: [PATCH] Fortran: deferred-length character optional dummy arguments
 [PR93762,PR100651]

gcc/fortran/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* trans-expr.cc (gfc_conv_missing_dummy): The character length for
	deferred-length dummy arguments is passed by reference, so that its
	value can be returned.  Adjust handling for optional dummies.

gcc/testsuite/ChangeLog:

	PR fortran/93762
	PR fortran/100651
	* gfortran.dg/optional_deferred_char_1.f90: New test.
---
 gcc/fortran/trans-expr.cc |  22 +++-
 .../gfortran.dg/optional_deferred_char_1.f90  | 100 ++
 2 files changed, 118 insertions(+), 4 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index bfe9996ced6..c90c7bbf936 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -2116,10 +2116,24 @@ gfc_conv_missing_dummy (gfc_se * se, gfc_expr * arg, gfc_typespec ts, int kind)
 
   if (ts.type == BT_CHARACTER)
 {
-  tmp = build_int_cst (gfc_charlen_type_node, 0);
-  tmp = fold_build3_loc (input_location, COND_EXPR, gfc_charlen_type_node,
-			 present, se->string_length, tmp);
-  tmp = gfc_evaluate_now (tmp, &se->pre);
+  /* Handle deferred-length dummies that pass the character length by
+	 reference so that the value can be returned.  */
+  if (ts.deferred && INDIRECT_REF_P (se->string_length))
+	{
+	  tmp = gfc_build_addr_expr (NULL_TREE, se->string_length);
+	  tmp = fold_build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp),
+ present, tmp, null_pointer_node);
+	  tmp = gfc_evaluate_now (tmp, &se->pre);
+	  tmp = build_fold_indirect_ref_loc (input_location, tmp);
+	}
+  else
+	{
+	  tmp = build_int_cst (gfc_charlen_type_node, 0);
+	  tmp = fold_build3_loc (input_location, COND_EXPR,
+ gfc_charlen_type_node,
+ present, se->string_length, tmp);
+	  tmp = gfc_evaluate_now (tmp, &se->pre);
+	}
   se->string_length = tmp;
 }
   return;
diff --git a/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90 b/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90
new file mode 100644
index 000..0fb0fb5fea1
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/optional_deferred_char_1.f90
@@ -0,0 +1,100 @@
+! { dg-do run }
+! PR fortran/93762
+! PR fortran/100651 - deferred-length character as optional dummy argument
+
+program main
+  implicit none
+  character(:), allocatable :: err_msg, msg3(:)
+  character(:), pointer :: err_msg2 => NULL()
+
+  ! Subroutines with optional arguments
+  call to_int ()
+  call to_int_p ()
+! call test_rank1 ()! this fails with -fsanitize=undefined
+  call assert_code ()
+  call assert_p ()
+  call assert_rank1 ()
+
+  ! Test passing of optional arguments
+  call to_int (err_msg)
+  if (.not. allocated (err_msg)) stop 1
+  if (len (err_msg) /= 7)stop 2
+  if (err_msg(1:7) /= "foo bar") stop 3
+
+  call to_int2 (err_msg)
+  if (.not. allocated (err_msg)) stop 4
+  if (l

[PATCH] Fortran: fix TARGET attribute of associating entity in ASSOCIATE [PR112764]

2023-11-29 Thread Harald Anlauf
Dear all,

the attached simple patch fixes the handling of the TARGET
attribute of an associate variable in an ASSOCIATE construct.

See e.g. F2018:11.1.3.3 for a standard reference.

(Note that the patch does not touch the pointer or allocatable
attributes, as that would lead to several testsuite regressions
and thus needs more work.)

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

Thanks,
Harald

From 023dc4691c73ed594d5c1085f1aab897ca4a7153 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Wed, 29 Nov 2023 21:47:24 +0100
Subject: [PATCH] Fortran: fix TARGET attribute of associating entity in
 ASSOCIATE [PR112764]

The associating entity in an ASSOCIATE construct has the TARGET attribute
if and only if the selector is a variable and has either the TARGET or
POINTER attribute (e.g. F2018:11.1.3.3).

gcc/fortran/ChangeLog:

	PR fortran/112764
	* primary.cc (gfc_variable_attr): Set TARGET attribute of associating
	entity dependent on TARGET or POINTER attribute of selector.

gcc/testsuite/ChangeLog:

	PR fortran/112764
	* gfortran.dg/associate_62.f90: New test.
---
 gcc/fortran/primary.cc | 16 ++
 gcc/testsuite/gfortran.dg/associate_62.f90 | 25 ++
 2 files changed, 41 insertions(+)
 create mode 100644 gcc/testsuite/gfortran.dg/associate_62.f90

diff --git a/gcc/fortran/primary.cc b/gcc/fortran/primary.cc
index d3aeeb89362..7278932b634 100644
--- a/gcc/fortran/primary.cc
+++ b/gcc/fortran/primary.cc
@@ -2653,6 +2653,22 @@ gfc_variable_attr (gfc_expr *expr, gfc_typespec *ts)
   if (pointer || attr.proc_pointer)
 target = 1;

+  /* F2018:11.1.3.3: Other attributes of associate names
+ "The associating entity does not have the ALLOCATABLE or POINTER
+ attributes; it has the TARGET attribute if and only if the selector is
+ a variable and has either the TARGET or POINTER attribute."  */
+  if (sym->attr.associate_var && sym->assoc && sym->assoc->target)
+{
+  if (sym->assoc->target->expr_type == EXPR_VARIABLE)
+	{
+	  symbol_attribute tgt_attr;
+	  tgt_attr = gfc_expr_attr (sym->assoc->target);
+	  target = (tgt_attr.pointer || tgt_attr.target);
+	}
+  else
+	target = 0;
+}
+
   if (ts != NULL && expr->ts.type == BT_UNKNOWN)
 *ts = sym->ts;

diff --git a/gcc/testsuite/gfortran.dg/associate_62.f90 b/gcc/testsuite/gfortran.dg/associate_62.f90
new file mode 100644
index 000..ce5bf286ee8
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/associate_62.f90
@@ -0,0 +1,25 @@
+! { dg-do compile }
+! PR fortran/112764
+! Contributed by martin 
+
+program assoc_target
+  implicit none
+  integer, dimension(:,:), pointer :: x
+  integer, pointer :: j
+  integer, allocatable, target :: z(:)
+  allocate (x(1:100,1:2), source=1)
+  associate (i1 => x(:,1))
+j => i1(1)
+print *, j
+if (j /= 1) stop 1
+  end associate
+  deallocate (x)
+  allocate (z(3))
+  z(:) = [1,2,3]
+  associate (i2 => z(2:3))
+j => i2(1)
+print *, j
+if (j /= 2) stop 2
+  end associate
+  deallocate (z)
+end program assoc_target
--
2.35.3



Re: testsuite: missing or wrong dg-* directives?

2013-01-13 Thread Harald Anlauf

On 01/12/13 22:02, Mikael Morin wrote:

Le 08/01/2013 22:32, Harald Anlauf a écrit :

On 12/28/12 21:49, Harald Anlauf wrote:

Hello all,

is there a default directive that is assumed when the testsuite is run?

Running an "fgrep -L" on the fortran testsuite, I found several files
that are missing either dg-do compile or run.

I also found a funny typo in gomp/appendix-a/a.11.2.f90
! { do-do compile }


find gfortran.dg -name "*.[fF]90" -o -name "*.[fF]" | \
xargs fgrep -w -L 'dg-do' | \
xargs head -1 -v

and manual inspection of the resulting output results in:

- Typos


[...]


- Possibly missing { dg-do run }


[...]

Mind sending patch and changelog to @gcc-patches ?



Here we go.  No failures, but additional passes because of the dg-do 
run's.  Somebody please take care of it?


Harald


2013-01-13  Harald Anlauf 

* gfortran.dg/aint_anint_1.f90: Add dg-do run.
* gfortran.dg/bounds_check_4.f90: Likewise.
* gfortran.dg/inquire_10.f90: Likewise.
* gfortran.dg/minloc_3.f90: Likewise.
* gfortran.dg/minlocval_3.f90: Likewise.
* gfortran.dg/module_double_reuse.f90: Likewise.
* gfortran.dg/mvbits_1.f90: Likewise.
* gfortran.dg/oldstyle_1.f90: Likewise.
* gfortran.dg/pr20163-2.f: Likewise.
* gfortran.dg/save_1.f90: Likewise.
* gfortran.dg/scan_1.f90: Likewise.
* gfortran.dg/select_char_1.f90: Likewise.
* gfortran.dg/shape_4.f90: Likewise.
* gfortran.dg/coarray_29_2.f90: Fix dg-do directive.
* gfortran.dg/function_optimize_10.f90: Likewise.
* gfortran.dg/gomp/appendix-a/a.11.2.f90: Likewise.
* gfortran.dg/used_types_17.f90: Likewise.
* gfortran.dg/used_types_18.f90: Likewise.

Index: gcc/testsuite/gfortran.dg/oldstyle_1.f90
===
--- gcc/testsuite/gfortran.dg/oldstyle_1.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/oldstyle_1.f90	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
   integer i, j /1/, g/2/, h ! { dg-warning "" "" }
   integer k, l(3) /2*2,1/   ! { dg-warning "" "" }
   real pi /3.1416/, e   ! { dg-warning "" "" }
Index: gcc/testsuite/gfortran.dg/scan_1.f90
===
--- gcc/testsuite/gfortran.dg/scan_1.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/scan_1.f90	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
 program b
integer w
character(len=2) s, t
Index: gcc/testsuite/gfortran.dg/aint_anint_1.f90
===
--- gcc/testsuite/gfortran.dg/aint_anint_1.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/aint_anint_1.f90	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
 program aint_anint_1
 
   implicit none
Index: gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90
===
--- gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/gomp/appendix-a/a.11.2.f90	(working copy)
@@ -1,4 +1,4 @@
-! { do-do compile }
+! { dg-do compile }
 
   SUBROUTINE A11_2(AA, BB, CC, DD, EE, FF, N)
   INTEGER N
Index: gcc/testsuite/gfortran.dg/bounds_check_4.f90
===
--- gcc/testsuite/gfortran.dg/bounds_check_4.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/bounds_check_4.f90	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
 subroutine foo(n,x)
   implicit none
   integer, intent(in) :: n
Index: gcc/testsuite/gfortran.dg/save_1.f90
===
--- gcc/testsuite/gfortran.dg/save_1.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/save_1.f90	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
 ! { dg-options "-O2 -fno-automatic" }
   subroutine foo (b)
 	logical b
Index: gcc/testsuite/gfortran.dg/coarray_29_2.f90
===
--- gcc/testsuite/gfortran.dg/coarray_29_2.f90	(revision 195136)
+++ gcc/testsuite/gfortran.dg/coarray_29_2.f90	(working copy)
@@ -1,4 +1,4 @@
-! { dg-compile }
+! { dg-do compile }
 ! { dg-options "-fcoarray=single" }
 
 ! Requires that coarray_29.f90 has been compiled before
Index: gcc/testsuite/gfortran.dg/pr20163-2.f
===
--- gcc/testsuite/gfortran.dg/pr20163-2.f	(revision 195136)
+++ gcc/testsuite/gfortran.dg/pr20163-2.f	(working copy)
@@ -1,3 +1,4 @@
+! { dg-do run }
open(10,status="foo",err=100) ! { dg-warning "STATUS specifier in OPEN statement .* has invalid value" }
call abort
   100  continue
Index: gcc/testsuite/gfortran.dg/minloc_3.f90
===
--- gcc/testsuite/g

Re: testsuite: missing or wrong dg-* directives?

2013-01-14 Thread Harald Anlauf

On 01/14/13 00:10, Manfred Schwarb wrote:

Am 13.01.2013 21:30, schrieb Harald Anlauf:

On 01/12/13 22:02, Mikael Morin wrote:

Le 08/01/2013 22:32, Harald Anlauf a écrit :

On 12/28/12 21:49, Harald Anlauf wrote:

Hello all,

is there a default directive that is assumed when the testsuite is
run?

Running an "fgrep -L" on the fortran testsuite, I found several files
that are missing either dg-do compile or run.

I also found a funny typo in gomp/appendix-a/a.11.2.f90
! { do-do compile }




There are several other oddities: d_g-final, braces have to be separated
by spaces.


Looking at the generated dump, tt appears that the occurence of
"d_g-final" is just some left-over junk and can be removed safely,
see below.  Maybe the author (Tobias B.) knows?


Not sure about the double braces in lto, I guess they act simply as
single braces.

class_array_10.f03:! { dg-do compile}
coarray_lib_token_4.f90:! { d_g-final { scan-tree-dump-times "bar
\\(&parm.\[0-9\]+, caf_token.\[0-9\]+, \\(\\(integer\\(kind=.\\)
parm.\[0-9\]+.data - \\(integer\\(kind=.\\)\\) x.\[0-9\]+\\) \\+
caf_offset.\[0-9\]+\\);" 1 "original" } }
continuation_9.f90:! { dg-warning "not allowed by itself in line 3" ""
{target "*-*-*"} 0 }
continuation_9.f90:! { dg-warning "not allowed by itself in line 4" ""
{target "*-*-*"} 0 }
continuation_9.f90:! { dg-warning "not allowed by itself in line 5" ""
{target "*-*-*"} 0 }
extends_11.f03:! { dg-final { scan-tree-dump-times "
+recruit\\.service\\.education\\.person\\.ss =" 8 "original"} }
lto/20091016-1_0.f90:! { dg-lto-options {{-flto -g -fPIC -r -nostdlib}
{-O -flto -g -fPIC -r -nostdlib}} }
lto/20100110-1_0.f90:! { dg-lto-options {{ -O1 -flto }} }
lto/pr41521_0.f90:! { dg-lto-options {{-g -flto} {-g -O -flto}} }
lto/pr46036_0.f90:! { dg-lto-options {{ -O -flto -ftree-vectorize }} }
lto/pr46629_0.f90:! { dg-lto-options {{ -O2 -flto -ftree-vectorize
-march=x86-64 }} { target i?86-*-* x86_64-*-* } }
lto/pr46629_0.f90:! { dg-lto-options {{ -O2 -flto -ftree-vectorize }} }
lto/pr46911_0.f:! { dg-lto-options {{ -O2 -flto -g }} }
lto/pr47839_0.f90:! { dg-lto-options {{ -g -flto }} }
move_alloc_13.f90:! { dg-do run}
structure_constructor_11.f90:! { dg-do run}
tab_continuation.f:! { dg-warning "Nonconforming tab character in column
1 of line 10" "Nonconforming tab" {target "*-*-*"} 0 }
tab_continuation.f:! { dg-warning "Nonconforming tab character in column
1 of line 11" "Nonconforming tab" {target "*-*-*"} 0 }
tab_continuation.f:! { dg-warning "Nonconforming tab character in column
1 of line 8" "Nonconforming tab" {target "*-*-*"} 0 }
tab_continuation.f:! { dg-warning "Nonconforming tab character in column
1 of line 9" "Nonconforming tab" {target "*-*-*"} 0 }
vect/vect-2.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using versioning." 3 "vect" {target { vect_no_align || { { !
vector_alignment_reachable  } && { ! vect_hw_misalign } } } } } }
vect/vect-3.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using peeling" 1 "vect" { xfail { vect_no_align || {!
vector_alignment_reachable}} } } }
vect/vect-3.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using versioning" 1 "vect" { target { {! vect_no_align} && { {!
vector_alignment_reachable} && {! vect_hw_misalign} } } } } }
vect/vect-3.f90:! { dg-final { scan-tree-dump-times "Vectorizing an
unaligned access" 1 "vect" { xfail { { vect_no_align } || { !
vector_alignment_reachable} } } } }
vect/vect-3.f90:! { dg-final { scan-tree-dump-times "Vectorizing an
unaligned access" 2 "vect" { target { {! vect_no_align} && { {!
vector_alignment_reachable} && {! vect_hw_misalign} } } } } }
vect/vect-4.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using peeling" 1 "vect" { xfail { { vect_no_align } || {!
vector_alignment_reachable} } } } }
vect/vect-4.f90:! { dg-final { scan-tree-dump-times "Vectorizing an
unaligned access" 1 "vect" { xfail { { vect_no_align } || {!
vector_alignment_reachable} } } } }
vect/vect-4.f90:! { dg-final { scan-tree-dump-times "Vectorizing an
unaligned access" 2 "vect" { target { {! vector_alignment_reachable} &&
{! vect_hw_misalign} } } } }
vect/vect-5.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using peeling" 1 "vect" { xfail { vect_no_align || {!
vector_alignment_reachable} } } } }
vect/vect-5.f90:! { dg-final { scan-tree-dump-times "Alignment of access
forced using versioning." 1 "vect" { target { {!
vector_align

[PATCH] PR/83874: ICE initializing character array from derived type

2018-01-17 Thread Harald Anlauf
The following obvious patch fixes a NULL pointer dereference:

Index: gcc/fortran/decl.c
===
--- gcc/fortran/decl.c  (revision 256671)
+++ gcc/fortran/decl.c  (working copy)
@@ -1718,7 +1718,7 @@
}
  else if (init->expr_type == EXPR_ARRAY)
{
- if (init->ts.u.cl)
+ if (init->ts.u.cl && init->ts.u.cl->length)
{
  const gfc_expr *length = init->ts.u.cl->length;
  if (length->expr_type != EXPR_CONSTANT)


Regtests without new failures on i686-pc-linux-gnu.
Testcase derived PR see below.

Whoever wants to take it, please commit to 8-trunk.
Due to the nature of the patch, it should be safe to backport
to the 6 and 7 branches.

Thanks,
Harald

---

Changelog:

2018-01-17  Harald Anlauf  

PR fortran/83874
* decl.c (add_init_expr_to_sym): Do not dereference NULL pointer.



Testsuite:

2018-01-17  Harald Anlauf  

PR fortran/83874
* gfortran.dg/pr83874.f90: New test.


Index: gfortran.dg/pr83874.f90
===
--- gfortran.dg/pr83874.f90 (revision 0)
+++ gfortran.dg/pr83874.f90 (revision 0)
@@ -0,0 +1,19 @@
+! { dg-do run }
+! PR fortran/83874
+! There was an ICE while initializing the character arrays
+!
+! Contributed by Harald Anlauf 
+!
+program charinit
+  implicit none
+  type t
+ character(len=1) :: name
+  end type t
+  type(t), parameter :: z(2)= [ t ('a'), t ('b') ]
+  character(len=1), parameter :: names1(*) = z% name
+  character(len=*), parameter :: names2(2) = z% name
+  character(len=*), parameter :: names3(*) = z% name
+  if (.not. (names1(1) == "a" .and. names1(2) == "b")) call abort ()
+  if (.not. (names2(1) == "a" .and. names2(2) == "b")) call abort ()
+  if (.not. (names3(1) == "a" .and. names3(2) == "b")) call abort ()
+end program charinit


[PATCH, fortran] PR/83864 - ICE in gfc_apply_init, at fortran/expr.c:4271

2018-01-17 Thread Harald Anlauf
The following obvious patch fixes a NULL pointer dereference:

Index: gcc/fortran/expr.c
===
--- gcc/fortran/expr.c  (revision 256671)
+++ gcc/fortran/expr.c  (working copy)
@@ -4267,7 +4269,7 @@
 gfc_set_constant_character_len (len, init, -1);
   else if (init
   && init->ts.type == BT_CHARACTER
-   && init->ts.u.cl
+   && init->ts.u.cl && init->ts.u.cl->length
&& mpz_cmp (ts->u.cl->length->value.integer,
init->ts.u.cl->length->value.integer))
 {

Regtests without new failures on i686-pc-linux-gnu.
Testcase derived from PR, see below.

Changelog:

2018-01-17  Harald Anlauf  

PR fortran/83864
* expr.c (add_init_expr_to_sym): Do not dereference NULL pointer.


Testcase:

2018-01-17  Harald Anlauf  

PR fortran/83864
* gfortran.dg/pr83864.f90: New test.


Index: gfortran.dg/pr83864.f90
===
--- gfortran.dg/pr83864.f90 (revision 0)
+++ gfortran.dg/pr83864.f90 (revision 0)
@@ -0,0 +1,13 @@
+! { dg-do run }
+! PR fortran/83864
+!
+! Derived from PR by Contributed by Gerhard Steinmetz 
+!
+program p
+  implicit none
+  type t
+ character :: c(3) = transfer('abc','z',3)
+  end type t
+  type(t) :: x
+  if (any (x%c /= ["a", "b", "c"])) call abort ()
+end

Whoever wants to commit this to 8-trunk, please do so.

Thanks,
Harald


[PATCH, fortran] PR71085 - ICE with some intrinsic functions specifying array function result dimension

2018-03-02 Thread Harald Anlauf
The fix to the PR probably counts as obvious, but here it is, along
with a testcase.  Changelogs below.

Regtested on i686-pc-linux-gnu.

Whoever reviews this, please feel free to commit.

Thanks,
Harald


2018-03-02  Harald Anlauf  

PR fortran/71085
* trans-expr.c (gfc_apply_interface_mapping_to_expr): Do not
dereference NULL pointer.


2018-03-02  Harald Anlauf  

PR fortran/71085
* gfortran.dg/pr71085.f90: New test.

Index: gcc/fortran/trans-expr.c
===
--- gcc/fortran/trans-expr.c(revision 258112)
+++ gcc/fortran/trans-expr.c(working copy)
@@ -4349,6 +4349,8 @@
 
   if (expr->value.function.esym == NULL
&& expr->value.function.isym != NULL
+   && expr->value.function.actual
+   && expr->value.function.actual->expr
&& expr->value.function.actual->expr->symtree
&& gfc_map_intrinsic_function (expr, mapping))
break;
Index: gcc/testsuite/gfortran.dg/pr71085.f90
===
--- gcc/testsuite/gfortran.dg/pr71085.f90   (revision 0)
+++ gcc/testsuite/gfortran.dg/pr71085.f90   (revision 0)
@@ -0,0 +1,12 @@
+! { dg-do compile }
+! PR 71085
+!
+! Testcase from PR by Vladimir Fuka 
+!
+program pr71085
+  print *, f()
+contains
+  function f()
+integer :: f(iargc()*10)
+  end
+end


[PATCH, fortran] PR84957 - [8 Regression] ICE in gfc_sym_type, at fortran/trans-types.c:2255

2018-03-21 Thread Harald Anlauf
The attached obvious patch fixes a NULL pointer dereference.
Testcase derived from report.  Changelogs below.

Regtested on i686-pc-linux-gnu.

Whoever reviews this, please feel free to commit.

Thanks,
Harald


2018-03-21  Harald Anlauf  

PR fortran/84957
* trans-types.c (gfc_sym_type): Do not dereference NULL pointer.


2018-03-21  Harald Anlauf  

PR fortran/84957
* gfortran.dg/pr84957.f90: New test.

Index: gcc/fortran/trans-types.c
===
--- gcc/fortran/trans-types.c   (revision 258740)
+++ gcc/fortran/trans-types.c   (working copy)
@@ -2252,6 +2252,7 @@
   && sym->ts.type == BT_CHARACTER
   && sym->ts.u.cl->backend_decl == NULL_TREE
   && sym->ns->proc_name
+  && sym->ns->proc_name->ts.u.cl
   && sym->ns->proc_name->ts.u.cl->backend_decl != NULL_TREE)
 sym->ts.u.cl->backend_decl = sym->ns->proc_name->ts.u.cl->backend_decl;
 
Index: gcc/testsuite/gfortran.dg/pr84957.f90
===
--- gcc/testsuite/gfortran.dg/pr84957.f90   (revision 0)
+++ gcc/testsuite/gfortran.dg/pr84957.f90   (revision 0)
@@ -0,0 +1,17 @@
+! { dg-do compile }
+! PR 84957
+!
+! Testcase derived from PR by G. Steinmetz  
+!
+function f() result(u)
+  entry g() result(v)
+contains
+  function v(x) result(z)
+character :: x(2)
+character(sum(len_trim(x))) :: z
+  end function v
+  function u(x) result(z)
+character :: x(2)
+character(sum(len_trim(x))) :: z
+  end function u
+end function f


[PATCH, fortran] PR85083 - [8 Regression] ICE in gfc_convert_to_structure_constructor, at fortran/primary.c:2915

2018-03-26 Thread Harald Anlauf
The attached obvious one-liner adds a missing check for type
compatibility in a structure constructor.

Testcase from report.  Changelogs below.

Regtested on i686-pc-linux-gnu.

Whoever reviews this, please feel free to commit.

Thanks,
Harald

2018-03-26  Harald Anlauf  

PR fortran/85083
* primary.c (gfc_convert_to_structure_constructor): Check
conformance of argument types in structure constructor.


2018-03-26  Harald Anlauf  

PR fortran/85083
* gfortran.dg/pr85083.f90: New test.

Index: gcc/fortran/primary.c
===
--- gcc/fortran/primary.c   (revision 258846)
+++ gcc/fortran/primary.c   (working copy)
@@ -2898,6 +2898,7 @@
   if (this_comp->ts.type == BT_CHARACTER && !this_comp->attr.allocatable
  && this_comp->ts.u.cl && this_comp->ts.u.cl->length
  && this_comp->ts.u.cl->length->expr_type == EXPR_CONSTANT
+ && actual->expr->ts.type == BT_CHARACTER
  && actual->expr->expr_type == EXPR_CONSTANT)
{
  ptrdiff_t c, e;
Index: gcc/testsuite/gfortran.dg/pr85083.f90
===
--- gcc/testsuite/gfortran.dg/pr85083.f90   (revision 0)
+++ gcc/testsuite/gfortran.dg/pr85083.f90   (revision 0)
@@ -0,0 +1,12 @@
+! { dg-do compile }
+! PR 85083
+!
+! Testcase from PR by G. Steinmetz  
+!
+program p
+  type t
+ character(3) :: c
+  end type t
+  type(t), allocatable :: z
+  allocate (z, source=t(.true.,'abc')) ! { dg-error "Too many components" }
+end


Re: [PATCH] Fortran: fix ICE in gfc_create_module_variable [PR100273]

2024-09-05 Thread Harald Anlauf

Thanks, Jerry.

Pushed as r15-3494-g1f462b5072a5e8 .

Am 05.09.24 um 21:46 schrieb Jerry D:

On 9/5/24 12:42 PM, Harald Anlauf wrote:

Dear all,

the attached simple patch fixes a corner case related to pr84868,
which was tracked separately.  While Paul's patch for pr84868 added
the framework for treating len_trim in the specification part of
a character function, it missed the possibility that that function
need not appear at the top level of a module, but could be a contained
function.

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

Thanks,
Harald



OK for mainline. Thanks.

Jerry






[PATCH] Fortran: fix ICE in gfc_create_module_variable [PR100273]

2024-09-05 Thread Harald Anlauf
Dear all,

the attached simple patch fixes a corner case related to pr84868,
which was tracked separately.  While Paul's patch for pr84868 added
the framework for treating len_trim in the specification part of
a character function, it missed the possibility that that function
need not appear at the top level of a module, but could be a contained
function.

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

Thanks,
Harald

From 1f462b5072a5e82c35921f7e3bdf3959c4a49dc9 Mon Sep 17 00:00:00 2001
From: Harald Anlauf 
Date: Thu, 5 Sep 2024 21:30:25 +0200
Subject: [PATCH] Fortran: fix ICE in gfc_create_module_variable [PR100273]

gcc/fortran/ChangeLog:

	PR fortran/100273
	* trans-decl.cc (gfc_create_module_variable): Handle module
	variable also when it is needed for the result specification
	of a contained function.

gcc/testsuite/ChangeLog:

	PR fortran/100273
	* gfortran.dg/pr100273.f90: New test.
---
 gcc/fortran/trans-decl.cc  |  3 ++-
 gcc/testsuite/gfortran.dg/pr100273.f90 | 26 ++
 2 files changed, 28 insertions(+), 1 deletion(-)
 create mode 100644 gcc/testsuite/gfortran.dg/pr100273.f90

diff --git a/gcc/fortran/trans-decl.cc b/gcc/fortran/trans-decl.cc
index 6692ac7ef4c..ee41d66e6d2 100644
--- a/gcc/fortran/trans-decl.cc
+++ b/gcc/fortran/trans-decl.cc
@@ -5540,7 +5540,8 @@ gfc_create_module_variable (gfc_symbol * sym)
   /* Create the variable.  */
   pushdecl (decl);
   gcc_assert (sym->ns->proc_name->attr.flavor == FL_MODULE
-	  || (sym->ns->parent->proc_name->attr.flavor == FL_MODULE
+	  || ((sym->ns->parent->proc_name->attr.flavor == FL_MODULE
+		   || sym->ns->parent->proc_name->attr.flavor == FL_PROCEDURE)
 		  && sym->fn_result_spec));
   DECL_CONTEXT (decl) = sym->ns->proc_name->backend_decl;
   rest_of_decl_compilation (decl, 1, 0);
diff --git a/gcc/testsuite/gfortran.dg/pr100273.f90 b/gcc/testsuite/gfortran.dg/pr100273.f90
new file mode 100644
index 000..f71947ad802
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr100273.f90
@@ -0,0 +1,26 @@
+! { dg-do compile }
+! PR fortran/100273 - ICE in gfc_create_module_variable
+!
+! Contributed by G.Steinmetz
+
+module m
+  implicit none
+contains
+  character(4) function g(k)
+integer :: k
+g = f(k)
+  contains
+function f(n)
+  character(3), parameter :: a(2) = ['1  ', '123']
+  integer :: n
+  character(len_trim(a(n))) :: f
+  f = 'abc'
+end
+  end
+end
+program p
+  use m
+  implicit none
+  print *, '>>' // g(1) // '<<'
+  print *, '>>' // g(2) // '<<'
+end
--
2.35.3



Re: [PATCH] PR libfortran/99218 - [8/9/10/11 Regression] matmul on temporary array accesses invalid memory

2021-03-05 Thread Harald Anlauf via Fortran
Dear all,

I finally figured out that the array dimensions simply need to be
large enough to get invalid memory accesses that actual lead to a
crash.

I will commit the following testcase along with the fix to libfortran:


! { dg-do run }
! PR libfortran/99218 - matmul on temporary array accesses invalid memory

program p
  implicit none
  integer, parameter :: nState = 30
  integer, parameter :: nCon = 1
  real,parameter :: ZERO = 0.0
  real :: G(nCon,nState) = ZERO
  real :: H(nState,nCon) = ZERO
  real :: lambda(nCon)   = ZERO
  real :: f(nState)  = ZERO
  f = matmul (transpose (G), lambda)
  if (f(1) /= ZERO) stop 1
end program


Cheers,
Harald



[PATCH] PR fortran/98411 - [10/11/12 Regression] Pointless warning for static variables

2021-05-10 Thread Harald Anlauf via Gcc-patches
A simple, self-explaining patch to avoid a wrong warning.

Regtested on x86_64-pc-linux-gnu.

OK for mainline?  Affected branches?

Thanks,
Harald


PR fortran/98411 - Pointless warning for static variables

Variables with explicit SAVE attribute cannot end up on the stack.
There is no point in checking whether they should be moved off the
stack to static storage.

gcc/fortran/ChangeLog:

PR fortran/98411
* trans-decl.c (gfc_finish_var_decl): Add check for explicit SAVE
attribute.

gcc/testsuite/ChangeLog:

PR fortran/98411
* gfortran.dg/pr98411.f90: New test.

diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index cc9d85543ca..7cded0a3ede 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -738,6 +738,7 @@ gfc_finish_var_decl (tree decl, gfc_symbol * sym)
   /* Keep variables larger than max-stack-var-size off stack.  */
   if (!(sym->ns->proc_name && sym->ns->proc_name->attr.recursive)
   && !sym->attr.automatic
+  && sym->attr.save != SAVE_EXPLICIT
   && INTEGER_CST_P (DECL_SIZE_UNIT (decl))
   && !gfc_can_put_var_on_stack (DECL_SIZE_UNIT (decl))
 	 /* Put variable length auto array pointers always into stack.  */
diff --git a/gcc/testsuite/gfortran.dg/pr98411.f90 b/gcc/testsuite/gfortran.dg/pr98411.f90
new file mode 100644
index 000..249afaea419
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr98411.f90
@@ -0,0 +1,16 @@
+! { dg-do compile }
+! { dg-options "-Wall -fautomatic -fmax-stack-var-size=100" }
+! PR fortran/98411 - Pointless warning for static variables
+
+module try
+  implicit none
+  integer, save :: a(1000)
+contains
+  subroutine initmodule
+real, save :: b(1000)
+logical:: c(1000) ! { dg-warning "moved from stack to static storage" }
+a(1) = 42
+b(2) = 3.14
+c(3) = .true.
+  end subroutine initmodule
+end module try


[PATCH] PR fortran/100602 - [11/12 Regression] Erroneous "pointer argument is not associated" runtime error

2021-05-18 Thread Harald Anlauf via Gcc-patches
The generation of the new runtime check picked up the wrong attributes
in the case of CLASS array arguments.  There is related new code in
gfc_conv_procedure_call which served as reference for the fix.

Regtested on x86_64-pc-linux-gnu.

OK for mainline / 11-branch?

Thanks,
Harald


Fortran: Fix erroneous "pointer argument is not associated" runtime error

For CLASS arrays we need to use the CLASS data attributes to determine
which runtime check to generate.

gcc/fortran/ChangeLog:

PR fortran/100602
* trans-intrinsic.c (gfc_conv_intrinsic_size): Use CLASS data
attributes for CLASS arrays for generation of runtime error.

gcc/testsuite/ChangeLog:

PR fortran/100602
* gfortran.dg/pointer_check_14.f90: New test.

diff --git a/gcc/fortran/trans-intrinsic.c b/gcc/fortran/trans-intrinsic.c
index 4d7451479d3..7ad297905b5 100644
--- a/gcc/fortran/trans-intrinsic.c
+++ b/gcc/fortran/trans-intrinsic.c
@@ -7999,7 +7999,14 @@ gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
   tree temp;
   tree cond;

-  attr = sym ? sym->attr : gfc_expr_attr (e);
+  if (e->symtree->n.sym && IS_CLASS_ARRAY (e->symtree->n.sym))
+	{
+	  attr = CLASS_DATA (e->symtree->n.sym)->attr;
+	  attr.pointer = attr.class_pointer;
+	}
+  else
+	attr = gfc_expr_attr (e);
+
   if (attr.allocatable)
 	msg = xasprintf ("Allocatable argument '%s' is not allocated",
 			 e->symtree->n.sym->name);
diff --git a/gcc/testsuite/gfortran.dg/pointer_check_14.f90 b/gcc/testsuite/gfortran.dg/pointer_check_14.f90
new file mode 100644
index 000..8ef6b3611fa
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pointer_check_14.f90
@@ -0,0 +1,28 @@
+! { dg-do run }
+! { dg-options "-fcheck=pointer -fdump-tree-original" }
+! PR100602 - Erroneous "pointer argument is not associated" runtime error
+
+module m
+  type :: T
+  end type
+contains
+  subroutine f(this)
+class(T), intent(in)  :: this(:)
+class(T), allocatable :: ca(:)
+class(T), pointer :: cp(:)
+if (size (this) == 0) return
+write(*,*) size (this)
+stop 1
+write(*,*) size (ca) ! Check #1
+write(*,*) size (cp) ! Check #2
+  end subroutine f
+end module
+
+program main
+  use m
+  call f([T::])
+end program
+
+! { dg-final { scan-tree-dump-times "_gfortran_runtime_error_at" 2 "original" } }
+! { dg-final { scan-tree-dump-times "Allocatable argument .*ca" 1 "original" } }
+! { dg-final { scan-tree-dump-times "Pointer argument .*cp" 1 "original" } }


Aw: [Patch] Testsuite/Fortran: gfortran.dg/pr96711.f90 - fix expected value for PowerPC [PR96983]

2021-05-19 Thread Harald Anlauf via Gcc-patches
Hi Tobias,

> @All, Harald: Does the attached patch make sense?

first of all: sorry for the really badly designed testcase.
The best solution has already been discussed in this thread,
which is to replace

  integer(16), parameter :: m1 = 9007199254740992_16!2**53
  integer(16), parameter :: m2 = 10384593717069655257060992658440192_16 !2**113

by

  integer(16), parameter :: m1 = 2_16 ** digits (x) ! IEEE: 2**53
  integer(16), parameter :: m2 = 2_16 ** digits (y) ! IEEE: 2**113

The motivation was to test that compile-time and run-time produce the
same correct result, as well as verifying that the user gets what he/she
would naively expect from the intrinsic.  There should be no hidden
double conversion that might e.g. truncate.

I decided for the largest real values which are exactly representable
also as integer, and for which the rounding operation should always
reproduce the expected result.

E.g.  nint (x) - nint (x-1) should give 1, while nint (x) - nint (x+1)
might give 0, which happens for the chosen values on x86.

I had this in my mind, but decided to drop this because I had no idea
if there are exotic, non-IEEE, or other implementations which would
fail on this.

Thanks for fixing this!

Harald



[PATCH] PR fortran/100551 - [11/12 Regression] Passing return value to class(*) dummy argument

2021-05-20 Thread Harald Anlauf via Gcc-patches
The fix for PR93924/5 has caused a regression for code such as given
in the present PR.  This can be remedied by adjusting the check when
to invoke the implicit conversion of actual argument to an unlimited
polymorphic procedure argument.

Regtested on x86_64-pc-linux-gnu.

OK for mainline and backport to 11-branch?

Thanks,
Harald


Fortran: fix passing return value to class(*) dummy argument

gcc/fortran/ChangeLog:

PR fortran/100551
* trans-expr.c (gfc_conv_procedure_call): Adjust check for
implicit conversion of actual argument to an unlimited polymorphic
procedure argument.

gcc/testsuite/ChangeLog:

PR fortran/100551
* gfortran.dg/pr100551.f90: New test.

diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index cce18d094a6..3432cd4fdfd 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -5826,7 +5826,9 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
  &derived_array);
 	}
   else if (UNLIMITED_POLY (fsym) && e->ts.type != BT_CLASS
-	   && gfc_expr_attr (e).flavor != FL_PROCEDURE)
+	   && e->ts.type != BT_PROCEDURE
+	   && (gfc_expr_attr (e).flavor != FL_PROCEDURE
+		   || gfc_expr_attr (e).proc != PROC_UNKNOWN))
 	{
 	  /* The intrinsic type needs to be converted to a temporary
 	 CLASS object for the unlimited polymorphic formal.  */
diff --git a/gcc/testsuite/gfortran.dg/pr100551.f90 b/gcc/testsuite/gfortran.dg/pr100551.f90
new file mode 100644
index 000..f82f505e734
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr100551.f90
@@ -0,0 +1,30 @@
+! { dg-do run }
+! PR fortran/100551 - Passing return value to class(*) dummy argument
+
+program p
+  implicit none
+  integer :: result
+  result = 1
+  result = test ((result)) ! works
+  if (result /= 1) stop 1
+  result = test (int (result)) ! issue 1
+! write(*,*) result
+  if (result /= 1) stop 2
+  result = test (f   (result)) ! issue 2
+! write(*,*) result
+  if (result /= 2) stop 3
+contains
+  integer function test(x)
+class(*), intent(in) :: x
+select type (x)
+type is (integer)
+   test = x
+class default
+   test = -1
+end select
+  end function test
+  integer function f(x)
+integer, intent(in) :: x
+f = 2*x
+  end function f
+end program


PING [PATCH] PR fortran/100602 - [11/12 Regression] Erroneous "pointer argument is not associated" runtime error

2021-05-25 Thread Harald Anlauf via Gcc-patches
*PING*

> Gesendet: Dienstag, 18. Mai 2021 um 20:36 Uhr
> Von: "Harald Anlauf" 
> An: "fortran" , "gcc-patches" 
> Betreff: [PATCH] PR fortran/100602 -  [11/12 Regression] Erroneous "pointer 
> argument is not associated" runtime error
>
> The generation of the new runtime check picked up the wrong attributes
> in the case of CLASS array arguments.  There is related new code in
> gfc_conv_procedure_call which served as reference for the fix.
>
> Regtested on x86_64-pc-linux-gnu.
>
> OK for mainline / 11-branch?
>
> Thanks,
> Harald
>
>
> Fortran: Fix erroneous "pointer argument is not associated" runtime error
>
> For CLASS arrays we need to use the CLASS data attributes to determine
> which runtime check to generate.
>
> gcc/fortran/ChangeLog:
>
>   PR fortran/100602
>   * trans-intrinsic.c (gfc_conv_intrinsic_size): Use CLASS data
>   attributes for CLASS arrays for generation of runtime error.
>
> gcc/testsuite/ChangeLog:
>
>   PR fortran/100602
>   * gfortran.dg/pointer_check_14.f90: New test.
>
>


[PATCH] PR fortran/100656 - ICE in gfc_conv_expr_present, at fortran/trans-expr.c:1934

2021-05-26 Thread Harald Anlauf via Gcc-patches
Dear Fortranners,

Gerhard found a case where bounds-checking for an optional,
allocatable character dummy resulted in an ICE.  We'd better
not call the presence check on a non-dummy symbol, as this
will hit an assert...

Regtested on x86_64-pc-linux-gnu.

OK for mainline?  And backport to 11?

(The code in question has not been touched for nearly 10 years,
so I'm expecting this to be safe).

Thanks,
Harald


PR fortran/100656 - prevent ICE in gfc_conv_expr_present

gcc/fortran/ChangeLog:

PR fortran/100656
* trans-array.c (gfc_conv_ss_startstride): Do not call check for
presence of a dummy argument when a symbol actually refers to a
non-dummy.

gcc/testsuite/ChangeLog:

PR fortran/100656
* gfortran.dg/bounds_check_22.f90: New test.

diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index 6d38ea78273..7eeef554c0f 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -4718,8 +4718,9 @@ done:

 	  /* For optional arguments, only check bounds if the argument is
 	 present.  */
-	  if (expr->symtree->n.sym->attr.optional
-	  || expr->symtree->n.sym->attr.not_always_present)
+	  if ((expr->symtree->n.sym->attr.optional
+	   || expr->symtree->n.sym->attr.not_always_present)
+	  && expr->symtree->n.sym->attr.dummy)
 	tmp = build3_v (COND_EXPR,
 			gfc_conv_expr_present (expr->symtree->n.sym),
 			tmp, build_empty_stmt (input_location));
diff --git a/gcc/testsuite/gfortran.dg/bounds_check_22.f90 b/gcc/testsuite/gfortran.dg/bounds_check_22.f90
new file mode 100644
index 000..a84e3dd4f51
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bounds_check_22.f90
@@ -0,0 +1,12 @@
+! { dg-do compile }
+! { dg-options "-fcheck=bounds" }
+! PR fortran/100656 - ICE in gfc_conv_expr_present
+
+subroutine s(x)
+  character(:), allocatable, optional :: x(:)
+  if ( present(x) ) then
+ if ( allocated(x) ) then
+x = 'a' // x // 'e'
+ end if
+  end if
+end


[PATCH] PR fortran/99839 - [9/10/11/12 Regression] ICE in inline_matmul_assign, at fortran/frontend-passes.c:4234

2021-05-27 Thread Harald Anlauf via Gcc-patches
Dear Fortranners,

frontend optimization tries to inline matmul, but then it also needs
to take care of the assignment to the result array.  If that one is
not of canonical type, we currently get an ICE.  The straightforward
solution is to simply punt in those cases and avoid inlining.

Regtested on x86_64-pc-linux-gnu.

OK for mainline?  Backport to affected branches?

Thanks,
Harald


Fortran - ICE in inline_matmul_assign

Restrict inlining of matmul to those cases where assignment to the
result array does not need special treatment.

gcc/fortran/ChangeLog:

PR fortran/99839
* frontend-passes.c (inline_matmul_assign): Do not inline matmul
if the assignment to the resulting array if it is not of canonical
type (real/integer/complex/logical).

gcc/testsuite/ChangeLog:

PR fortran/99839
* gfortran.dg/inline_matmul_25.f90: New test.

diff --git a/gcc/fortran/frontend-passes.c b/gcc/fortran/frontend-passes.c
index ffe2db4881d..8aa4cf0eca7 100644
--- a/gcc/fortran/frontend-passes.c
+++ b/gcc/fortran/frontend-passes.c
@@ -4193,6 +4193,19 @@ inline_matmul_assign (gfc_code **c, int *walk_subtrees,
   if (m_case == none)
 return 0;

+  /* We only handle assignment to numeric or logical variables.  */
+  switch(expr1->ts.type)
+{
+case BT_INTEGER:
+case BT_LOGICAL:
+case BT_REAL:
+case BT_COMPLEX:
+  break;
+
+default:
+  return 0;
+}
+
   ns = insert_block ();

   /* Assign the type of the zero expression for initializing the resulting
diff --git a/gcc/testsuite/gfortran.dg/inline_matmul_25.f90 b/gcc/testsuite/gfortran.dg/inline_matmul_25.f90
new file mode 100644
index 000..df8ad06c123
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/inline_matmul_25.f90
@@ -0,0 +1,9 @@
+! { dg-do compile }
+! { dg-options "-ffrontend-optimize" }
+! PR fortran/99839 - ICE in inline_matmul_assign
+
+program p
+  real :: x(3, 3) = 1.0
+  class(*), allocatable :: z(:, :)
+  z = matmul(x, x)
+end


PING [PATCH] PR fortran/99839 - [9/10/11/12 Regression] ICE in inline_matmul_assign, at fortran/frontend-passes.c:4234

2021-06-03 Thread Harald Anlauf via Gcc-patches
*PING*

> Gesendet: Donnerstag, 27. Mai 2021 um 22:20 Uhr
> Von: "Harald Anlauf" 
> An: "fortran" , "gcc-patches" 
> Betreff: [PATCH] PR fortran/99839 - [9/10/11/12 Regression] ICE in 
> inline_matmul_assign, at fortran/frontend-passes.c:4234
>
> Dear Fortranners,
>
> frontend optimization tries to inline matmul, but then it also needs
> to take care of the assignment to the result array.  If that one is
> not of canonical type, we currently get an ICE.  The straightforward
> solution is to simply punt in those cases and avoid inlining.
>
> Regtested on x86_64-pc-linux-gnu.
>
> OK for mainline?  Backport to affected branches?
>
> Thanks,
> Harald
>
>
> Fortran - ICE in inline_matmul_assign
>
> Restrict inlining of matmul to those cases where assignment to the
> result array does not need special treatment.
>
> gcc/fortran/ChangeLog:
>
>   PR fortran/99839
>   * frontend-passes.c (inline_matmul_assign): Do not inline matmul
>   if the assignment to the resulting array if it is not of canonical
>   type (real/integer/complex/logical).
>
> gcc/testsuite/ChangeLog:
>
>   PR fortran/99839
>   * gfortran.dg/inline_matmul_25.f90: New test.
>
>


[PATCH] PR fortran/95502 - ICE in gfc_check_do_variable, at fortran/parse.c:4446

2021-06-04 Thread Harald Anlauf via Gcc-patches
ICE-on-invalid issues during error recovery.  Testcase by Gerhard,
initial patch by Steve.  I found another variant which needed an
additional fix for a NULL pointer dereference.

Regtested on x86_64-pc-linux-gnu.

OK for mainline / 11-branch?

Thanks,
Harald


Fortran - ICE in gfc_check_do_variable, at fortran/parse.c:4446

Avoid NULL pointer dereferences during error recovery.

gcc/fortran/ChangeLog:

PR fortran/95502
* expr.c (gfc_check_pointer_assign): Avoid NULL pointer
dereference.
* match.c (gfc_match_pointer_assignment): Likewise.
* parse.c (gfc_check_do_variable): Avoid comparison with NULL
symtree.

gcc/testsuite/ChangeLog:

PR fortran/95502
* gfortran.dg/pr95502.f90: New test.

diff --git a/gcc/fortran/expr.c b/gcc/fortran/expr.c
index 956003ec605..b11ae7ce5c5 100644
--- a/gcc/fortran/expr.c
+++ b/gcc/fortran/expr.c
@@ -3815,6 +3815,9 @@ gfc_check_pointer_assign (gfc_expr *lvalue, gfc_expr *rvalue,
   int proc_pointer;
   bool same_rank;

+  if (!lvalue->symtree)
+return false;
+
   lhs_attr = gfc_expr_attr (lvalue);
   if (lvalue->ts.type == BT_UNKNOWN && !lhs_attr.proc_pointer)
 {
diff --git a/gcc/fortran/match.c b/gcc/fortran/match.c
index 29462013038..d148de3e3b5 100644
--- a/gcc/fortran/match.c
+++ b/gcc/fortran/match.c
@@ -1409,7 +1409,7 @@ gfc_match_pointer_assignment (void)
   gfc_matching_procptr_assignment = 0;

   m = gfc_match (" %v =>", &lvalue);
-  if (m != MATCH_YES)
+  if (m != MATCH_YES || !lvalue->symtree)
 {
   m = MATCH_NO;
   goto cleanup;
diff --git a/gcc/fortran/parse.c b/gcc/fortran/parse.c
index 0522b391393..6d7845e8517 100644
--- a/gcc/fortran/parse.c
+++ b/gcc/fortran/parse.c
@@ -4588,6 +4588,9 @@ gfc_check_do_variable (gfc_symtree *st)
 {
   gfc_state_data *s;

+  if (!st)
+return 0;
+
   for (s=gfc_state_stack; s; s = s->previous)
 if (s->do_variable == st)
   {
diff --git a/gcc/testsuite/gfortran.dg/pr95502.f90 b/gcc/testsuite/gfortran.dg/pr95502.f90
new file mode 100644
index 000..d40fd9a5508
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr95502.f90
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! PR fortran/95502 - ICE in gfc_check_do_variable, at fortran/parse.c:4446
+
+program p
+  integer, pointer :: z
+  nullify (z%kind)  ! { dg-error "in variable definition context" }
+  z%kind => NULL()  ! { dg-error "constant expression" }
+end


[PATCH] PR fortran/78746 - invalid access after error recovery

2021-01-05 Thread Harald Anlauf via Gcc-patches
Dear all,

the PR contains a lengthy discussion of several testcases, some which were
considered invalid and thus removed from the testsuite (charlen_03.f90,
charlen_10.f90), charlen_15.f90 was resolved elsewhere, so that only
class_61.f90 was left with an invalid access after error recovery with
an instrumented compiler.

I could reproduce the issue triggered by class_61.f90 using valgrind,
and found that the attached trivial, almost obvious patch solves it.
It even regtests cleanly on x86_64-pc-linux-gnu.

OK for master?  Open branches where testcase class_61.f90 exists?

Thanks,
Harald


PR fortran/78746 - invalid access after error recovery

The error recovery after an invalid reference to an undefined CLASS
during a TYPE declaration lead to an invalid access.  Add a check.

gcc/fortran/ChangeLog:

* resolve.c (resolve_component): Add check for valid CLASS
reference before trying to access CLASS data.

diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index fa6f756d285..891db391907 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -14384,7 +14396,7 @@ resolve_component (gfc_component *c, gfc_symbol *sym)
   /* F2008, C448.  */
   if (c->ts.type == BT_CLASS)
 {
-  if (CLASS_DATA (c))
+  if (c->attr.class_ok && CLASS_DATA (c))
 	{
 	  attr = &(CLASS_DATA (c)->attr);



[Patch, RFC] PR fortran/93340 - [8/9/10/11 Regression] fix missed substring simplifications

2021-01-12 Thread Harald Anlauf via Gcc-patches
Dear all,

when playing around with the issues exposed by PR93340, particularly visible
in the tree dump, I tried to find ways to simplify substrings in those cases
where they are eligible as designator, which is required e.g. in DATA 
statements.

Given my limited understanding, I finally arrived at a potential solution which
does that simplification near the end of match_string_constant in primary.c.
I couldn't find a better place, but I am open to better suggestions.

The simplification below does an even better job at detecting invalid substring
starting or ending indices than HEAD, and regtests cleanly on 
x86_64-pc-linux-gnu.

Feedback appreciated.  Is this potentially ok for master, or should this be done
differently?

Thanks,
Harald


PR fortran/93340 - fix missed substring simplifications

Substrings were not reduced early enough for use in initializations,
such as DATA statements.  Add an early simplification for substrings
with constant starting and ending points.

gcc/fortran/ChangeLog:

* gfortran.h (gfc_resolve_substring): Add prototype.
* primary.c (match_string_constant): Simplify substrings with
constant starting and ending points.
* resolve.c: Rename resolve_substring to gfc_resolve_substring.
(gfc_resolve_ref): Use renamed function gfc_resolve_substring.

gcc/testsuite/ChangeLog:

* substr_10.f90: New test.
* substr_9.f90: New test.

diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 6585e4f3ecd..4dd72b620c9 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -3467,6 +3467,7 @@ bool find_forall_index (gfc_expr *, gfc_symbol *, int);
 bool gfc_resolve_index (gfc_expr *, int);
 bool gfc_resolve_dim_arg (gfc_expr *);
 bool gfc_is_formal_arg (void);
+bool gfc_resolve_substring (gfc_ref *, bool *);
 void gfc_resolve_substring_charlen (gfc_expr *);
 match gfc_iso_c_sub_interface(gfc_code *, gfc_symbol *);
 gfc_expr *gfc_expr_to_initialize (gfc_expr *);
diff --git a/gcc/fortran/primary.c b/gcc/fortran/primary.c
index db9ecf9a4f6..7cb378e3090 100644
--- a/gcc/fortran/primary.c
+++ b/gcc/fortran/primary.c
@@ -1190,6 +1190,61 @@ got_delim:
   if (match_substring (NULL, 0, &e->ref, false) != MATCH_NO)
 e->expr_type = EXPR_SUBSTRING;

+  /* Substrings with constant starting and ending points are eligible as
+ designators (F2018, section 9.1).  Simplify substrings to make them usable
+ e.g. in data statements.  */
+  if (e->expr_type == EXPR_SUBSTRING
+  && e->ref && e->ref->type == REF_SUBSTRING
+  && e->ref->u.ss.start->expr_type == EXPR_CONSTANT
+  && (e->ref->u.ss.end == NULL
+	  || e->ref->u.ss.end->expr_type == EXPR_CONSTANT))
+{
+  gfc_expr *res;
+  ptrdiff_t istart, iend;
+  size_t length;
+  bool equal_length = false;
+
+  /* Basic checks on substring  starting and ending indices.  */
+  if (!gfc_resolve_substring (e->ref, &equal_length))
+	return MATCH_ERROR;
+
+  length = e->value.character.length;
+  istart = gfc_mpz_get_hwi (e->ref->u.ss.start->value.integer);
+  if (e->ref->u.ss.end == NULL)
+	iend = length;
+  else
+	iend = gfc_mpz_get_hwi (e->ref->u.ss.end->value.integer);
+
+  if (istart <= iend)
+	{
+	  if (istart < 1)
+	{
+	  gfc_error ("Substring start index (%ld) at %L below 1",
+			 (long) istart, &e->ref->u.ss.start->where);
+	  return MATCH_ERROR;
+	}
+	  if (iend > (ssize_t) length)
+	{
+	  gfc_error ("Substring end index (%ld) at %L exceeds string "
+			 "length", (long) iend, &e->ref->u.ss.end->where);
+	  return MATCH_ERROR;
+	}
+	  length = iend - istart + 1;
+	}
+  else
+	length = 0;
+
+  res = gfc_get_constant_expr (BT_CHARACTER, e->ts.kind, &e->where);
+  res->value.character.string = gfc_get_wide_string (length + 1);
+  res->value.character.length = length;
+  if (length > 0)
+	memcpy (res->value.character.string,
+		&e->value.character.string[istart - 1],
+		length * sizeof (gfc_char_t));
+  res->value.character.string[length] = '\0';
+  e = res;
+}
+
   *result = e;

   return MATCH_YES;
diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index f243bd185b0..3929ddff849 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -5068,8 +5068,8 @@ resolve_array_ref (gfc_array_ref *ar)
 }


-static bool
-resolve_substring (gfc_ref *ref, bool *equal_length)
+bool
+gfc_resolve_substring (gfc_ref *ref, bool *equal_length)
 {
   int k = gfc_validate_kind (BT_INTEGER, gfc_charlen_int_kind, false);

@@ -5277,7 +5277,7 @@ gfc_resolve_ref (gfc_expr *expr)

   case REF_SUBSTRING:
 	equal_length = false;
-	if (!resolve_substring (*prev, &equal_length))
+	if (!gfc_resolve_substring (*prev, &equal_length))
 	  return false;

 	if (expr->expr_type != EXPR_SUBSTRING && equal_length)
diff --git a/gcc/testsuite/substr_10.f90 b/gcc/testsuite/substr_10.f90
new file mode 100644
index 000..918ca8af162
--- /dev/null
+++ b/gcc/testsuite/substr_1

[PATCH] PR fortran/98661 - valgrind issues with error recovery

2021-01-13 Thread Harald Anlauf via Gcc-patches
Dear all,

the former Fortran testcase charlen_03.f90, which some time ago used to
ICE, could still display issues during error recovery.  As Dominique
pointed out, this required either an instrumented compiler, or valgrind.

The issue turned out to not have anything to do with CHARACTER, but
with an invalid attempt resolve an invalid array specification.

Regtested on x86_64-pc-linux-gnu, and checked for the testcase with valgrind.

OK for master?

Thanks,
Harald


PR fortran/98661 - valgrind issues with error recovery

During error recovery after an invalid derived type specification it was
possible to try to resolve an invalid array specification.  We now skip
this if the component has the ALLOCATABLE or POINTER attribute and the
shape is not deferred.

gcc/fortran/ChangeLog:

PR fortran/98661
* resolve.c (resolve_component): Derived type components with
ALLOCATABLE or POINTER attribute shall have a deferred shape.

gcc/testsuite/ChangeLog:

PR fortran/98661
* gfortran.dg/pr98661.f90: New test.

diff --git a/gcc/fortran/resolve.c b/gcc/fortran/resolve.c
index 3929ddff849..448a2362e95 100644
--- a/gcc/fortran/resolve.c
+++ b/gcc/fortran/resolve.c
@@ -14723,6 +14735,10 @@ resolve_component (gfc_component *c, gfc_symbol *sym)
 && sym != c->ts.u.derived)
 add_dt_to_dt_list (c->ts.u.derived);

+  if (c->as && c->as->type != AS_DEFERRED
+  && (c->attr.pointer || c->attr.allocatable))
+return false;
+
   if (!gfc_resolve_array_spec (c->as,
!(c->attr.pointer || c->attr.proc_pointer
  || c->attr.allocatable)))
diff --git a/gcc/testsuite/gfortran.dg/pr98661.f90 b/gcc/testsuite/gfortran.dg/pr98661.f90
new file mode 100644
index 000..40ddff05d43
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr98661.f90
@@ -0,0 +1,19 @@
+! { dg-do compile }
+! PR fortran/98661 - valgrind issues with error recovery
+!
+! Test issues related to former testcase charlen_03.f90
+program p
+  implicit none
+  type t
+ character(:), pointer :: c(n) ! { dg-error "must have a deferred shape" }
+ real, allocatable :: x(n) ! { dg-error "must have a deferred shape" }
+  end type
+end
+
+subroutine s
+! no 'implicit none'
+  type u
+ character(:), pointer :: c(n) ! { dg-error "must have a deferred shape" }
+ real, allocatable :: x(n) ! { dg-error "must have a deferred shape" }
+  end type
+end


[PATCH] PR fortran/70070 - ICE on initializing character data beyond min/max bound

2021-01-24 Thread Harald Anlauf via Gcc-patches
Dear all,

the attached patch is pretty much self-explaining: check for bounds violation
when initializing a substring in a data statement and treat the resulting error.

If more detailed information should be emitted with the error message, I'm
open for suggestions.

Regtested on x86_64-pc-linux-gnu.

OK for master?

Thanks,
Harald


PR fortran/70070 - ICE on initializing character data beyond min/max bound

Check for initialization of substrings beyond bounds in DATA statements.

gcc/fortran/ChangeLog:

PR fortran/70070
* data.c (create_character_initializer): Check substring indices
against bounds.
(gfc_assign_data_value): Catch error returned from
create_character_initializer.

gcc/testsuite/ChangeLog:

PR fortran/70070
* gfortran.dg/pr70070.f90: New test.

diff --git a/gcc/fortran/data.c b/gcc/fortran/data.c
index 1313b335c86..d9f0b45da9b 100644
--- a/gcc/fortran/data.c
+++ b/gcc/fortran/data.c
@@ -183,6 +183,13 @@ create_character_initializer (gfc_expr *init, gfc_typespec *ts,
 	}
 }

+  if (start < 0 || end > init->value.character.length)
+{
+  gfc_error ("Invalid substring in DATA statement at %L",
+		 &ref->u.ss.start->where);
+  return NULL;
+}
+
   if (rvalue->ts.type == BT_HOLLERITH)
 {
   for (size_t i = 0; i < (size_t) len; i++)
@@ -576,6 +583,8 @@ gfc_assign_data_value (gfc_expr *lvalue, gfc_expr *rvalue, mpz_t index,
   if (lvalue->ts.u.cl->length == NULL && !(ref && ref->u.ss.length != NULL))
 	return false;
   expr = create_character_initializer (init, last_ts, ref, rvalue);
+  if (!expr)
+	return false;
 }
   else
 {
diff --git a/gcc/testsuite/gfortran.dg/pr70070.f90 b/gcc/testsuite/gfortran.dg/pr70070.f90
new file mode 100644
index 000..c79cd229552
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr70070.f90
@@ -0,0 +1,8 @@
+! { dg-do compile }
+! PR fortran/70070 - ICE on initializing character data beyond min/max bound
+
+program p
+  character(1) :: a, b
+  data (a(i:i),i=0,0) /1*'#'/   ! { dg-error "Invalid substring" }
+  data (b(i:i),i=1,2) /2*'#'/   ! { dg-error "Invalid substring" }
+end


Re: [PATCH] PR fortran/70070 - ICE on initializing character data beyond min/max bound

2021-01-25 Thread Harald Anlauf via Gcc-patches
Hi Thomas,

> Gesendet: Montag, 25. Januar 2021 um 19:58 Uhr
> Von: "Thomas Koenig" 

> a.f90:3:10:
>
>  3 |   print a(0:3)
>|  1
> Error: Substring start index at (1) is less than one
> a.f90:4:10:
>
>  4 |   print a(1:4)
>|  1
> Error: Substring end index at (1) exceeds the string length
>
> Could you maybe just re-use these?

this is done in the attached patch.  Committed and pushed to master.

> OK with adjusted error message.  Thanks for the patch!

Thanks for the review!

Harald



pr70070.patch-v2
Description: Binary data


[PATCH] [8/9/10/11 Regression] [OOP] PR fortran/86470 - ICE with OpenMP

2021-01-27 Thread Harald Anlauf via Gcc-patches
Dear all,

the fix for this ICE is obvious: make gfc_call_malloc behave as documented.
Apparently the special case in question was not exercised in the testsuite.

Regtested on x86_64-pc-linux-gnu.

OK for master / backports?

Should the testcase be moved to the gomp/ subdirectory?

Thanks,
Harald


PR fortran/86470 - ICE with OpenMP, class(*) allocatable

gfc_call_malloc should malloc an area of size 1 if no size given.

gcc/fortran/ChangeLog:

PR fortran/86470
* trans.c (gfc_call_malloc): Allocate area of size 1 if passed
size is NULL (as documented).

gcc/testsuite/ChangeLog:

PR fortran/86470
* gfortran.dg/pr86470.f90: New test.

diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c
index a2376917635..ab53fc5f441 100644
--- a/gcc/fortran/trans.c
+++ b/gcc/fortran/trans.c
@@ -689,6 +689,9 @@ gfc_call_malloc (stmtblock_t * block, tree type, tree size)
   /* Call malloc.  */
   gfc_start_block (&block2);

+  if (size == NULL_TREE)
+size = build_int_cst (size_type_node, 1);
+
   size = fold_convert (size_type_node, size);
   size = fold_build2_loc (input_location, MAX_EXPR, size_type_node, size,
 			  build_int_cst (size_type_node, 1));
diff --git a/gcc/testsuite/gfortran.dg/pr86470.f90 b/gcc/testsuite/gfortran.dg/pr86470.f90
new file mode 100644
index 000..4021e5d655c
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr86470.f90
@@ -0,0 +1,13 @@
+! { dg-do compile }
+! { dg-options "-fopenmp" }
+! PR fortran/86470 - ICE with OpenMP, class(*)
+
+program p
+  implicit none
+  class(*), allocatable :: val
+!$OMP PARALLEL private(val)
+  allocate(integer::val)
+  val = 1
+  deallocate(val)
+!$OMP END PARALLEL
+end


Re: [PATCH] [8/9/10/11 Regression] [OOP] PR fortran/86470 - ICE with OpenMP

2021-01-28 Thread Harald Anlauf via Gcc-patches
Hi Thomas,

> > Should the testcase be moved to the gomp/ subdirectory?
> Yes. It's a compile-time test, and it will then only be run
> if the the compiler can do OpenMP.
>
> You will not need the
>
> +! { dg-options "-fopenmp" }
>
> line, then.

Adjusted and committed as r11-6950-g33a7a93218b1393d0135e3c4a9ad9ced87808f5e

> Thanks for the patch!

Thanks,
Harald



[PATCH] PR fortran/99147 - Sanitizer detects heap-use-after-free in gfc_add_flavor

2021-02-18 Thread Harald Anlauf via Gcc-patches
Dear all,

the PR reports an issue detected with an ASAN instrumented compiler,
which can also be verified with valgrind.  It appears that the state
of gfc_new_block could be such that it should not be dereferenced.
Reversing the order of condition evaluation helped.

I failed to find out why this should happen, but then other places
in the code put dereferences of gfc_new_block behind other checks.
Simple things like initializing gfc_new_block with NULL in decl.c
did not help.

Regtested on x86_64-pc-linux-gnu.  No testcase added since the issue
can be found only with an instrumented compiler or valgrind.

I consider the patch to be obvious and trivial, but post it here
in case somebody wants to dig deeper.

OK for master?

Thanks,
Harald


PR fortran/99147 - Sanitizer detects heap-use-after-free in gfc_add_flavor

Reverse order of conditions to avoid invalid read.

gcc/fortran/ChangeLog:

* symbol.c (gfc_add_flavor): Reverse order of conditions.

diff --git a/gcc/fortran/symbol.c b/gcc/fortran/symbol.c
index 3b988d1be22..e982374d9d1 100644
--- a/gcc/fortran/symbol.c
+++ b/gcc/fortran/symbol.c
@@ -1772,8 +1772,8 @@ gfc_add_flavor (symbol_attribute *attr, sym_flavor f, const char *name,
   /* Copying a procedure dummy argument for a module procedure in a
  submodule results in the flavor being copied and would result in
  an error without this.  */
-  if (gfc_new_block && gfc_new_block->abr_modproc_decl
-  && attr->flavor == f && f == FL_PROCEDURE)
+  if (attr->flavor == f && f == FL_PROCEDURE
+  && gfc_new_block && gfc_new_block->abr_modproc_decl)
 return true;

   if (attr->flavor != FL_UNKNOWN)


[PATCH] PR fortran/99169 - [9/10/11 Regression] Segfault when passing allocatable scalar into intent(out) dummy argument

2021-02-19 Thread Harald Anlauf via Gcc-patches
Dear all,

we should not clobber the pointer in case of an allocatable scalar being
an intent(out) dummy argument to a procedure.

Regtested on x86_64-pc-linux-gnu.

OK for master?  Since this is a regression, also for backports to 10/9?

Thanks,
Harald


PR fortran/99169 - Do not clobber allocatable intent(out) dummy argument

gcc/fortran/ChangeLog:

* trans-expr.c (gfc_conv_procedure_call): Do not add clobber to
allocatable intent(out) argument.

gcc/testsuite/ChangeLog:

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

diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 103cb31c664..cab58cd1bba 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -6077,6 +6079,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
 			&& !fsym->attr.allocatable && !fsym->attr.pointer
 			&& !e->symtree->n.sym->attr.dimension
 			&& !e->symtree->n.sym->attr.pointer
+			&& !e->symtree->n.sym->attr.allocatable
 			/* See PR 41453.  */
 			&& !e->symtree->n.sym->attr.dummy
 			/* FIXME - PR 87395 and PR 41453  */
diff --git a/gcc/testsuite/gfortran.dg/intent_optimize_3.f90 b/gcc/testsuite/gfortran.dg/intent_optimize_3.f90
new file mode 100644
index 000..6ecd722da76
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/intent_optimize_3.f90
@@ -0,0 +1,16 @@
+! { dg-do run }
+! { dg-options "-O2" }
+! PR99169 - Segfault passing allocatable scalar into intent(out) dummy argument
+
+program p
+  implicit none
+  integer, allocatable :: i
+  allocate (i)
+  call set (i)
+  if (i /= 5) stop 1
+contains
+  subroutine set (i)
+integer, intent(out) :: i
+i = 5
+  end subroutine set
+end program p


<    1   2   3   4   5   6   7   8   9   10   >