[Patch, fortran] PRs 105152, 100193, 87946, 103389, 104429 and 82774

2023-04-22 Thread Paul Richard Thomas via Fortran
Hi All,

As usual, I received a string of emails on retargeting for PRs for which I
was either responsible or was on the cc list. This time I decided to take a
look at them all, in order to reward the tireless efforts of Richi, Jakub
and Martin with some attention at least.

I have fixed the PRs in the title line: See the attached changelog, patch
and testcases.

OK for 14-branch?

Of the others:
PR100815 - fixed already for 12-branch on. Martin located the fix from
Tobias, for which thanks. It's quite large but has stood the test of time.
Should I backport to 11-branch?
PR103366 - fixed on 12-branch on. I closed it.
PR103715 - might be fixed but the report is for gcc with checking enabled.
I will give that a go.
PR103716 - a gimple problem with assumed shape characters. A TODO.
PR103931 - I couldn't reproduce the bug, which involves 'ambiguous c_ptr'.
To judge by the comments, it seems that this bug is a bit elusive.
PR65381 - Seems to be fixed for 12-branch on
PR82064 - Seems to be fixed.
PR83209 - Coarray allocation - seems to be fixed.
PR84244 - Coarray segfault. I have no acquaintance with the inner works of
coarrays and so don't think that I can fix this one.
PR87674 - Segfault in runtime with non-overridable proc-pointer. A TODO.
PR96087 - A module procedure problem. A TODO.

I have dejagnu-ified testcases for the already fixed PRs ready to go.
Should these be committed or do we assume that the fixes already provided
adequate tests?

Regards

Paul
! { dg-do compile }
!
! Contributed by Gerhard Steinmetz  
!
program p
   use iso_c_binding
   type, bind(c) :: t
  integer(c_int) :: a
   end type
   interface
  function f(x) bind(c) result(z)
 import :: c_int, t
 type(t) :: x(:)
 integer(c_int) :: z
  end
   end interface
   class(*), allocatable :: y(:)
   n = f(y) ! { dg-error "either an unlimited polymorphic or assumed type" }
end
! { dg-do compile }
!
! Contributed by Gerhard Steinmetz  
!
module m
   implicit none
   type t
  procedure(f), pointer, nopass :: g
   end type
contains
   function f()
  character(:), allocatable :: f
  f = 'abc'
   end
   subroutine s
  type(t) :: z
  z%g = 'x'  ! { dg-error "is a procedure pointer" }
  if ( z%g() /= 'abc' ) stop
   end
end
program p
   use m
   implicit none
   call s
end
! { dg-do run }
!
! Contributed by Gerhard Steinmetz  
!
module m
   type t
   contains
  generic :: h => g
  procedure, private :: g
   end type
contains
   function g(x, y) result(z)
  class(t), intent(in) :: x
  real, intent(in) :: y(:, :)
  real :: z(size(y, 2))
  integer :: i
  do i = 1, size(y, 2)
z(i) = i
  end do
   end
end
module m2
   use m
   type t2
  class(t), allocatable :: u(:)
   end type
end
   use m2
   type(t2) :: x
   real :: y(1,5)
   allocate (x%u(1))
   if (any (int(f (x, y)) .ne. [1,2,3,4,5])) stop 1
   deallocate (x%u)
contains
   function f(x, y) result(z)
  use m2
  type(t2) :: x
  real :: y(:, :)
  real :: z(size(y, 2))
  z = x%u(1)%h(y)  ! Used to segfault here
   end
end
! { dg-do run }
!
! Contributed by Gerhard Steinmetz  
!
program p
   type t
  integer, allocatable :: a(:)
   end type
   type(t) :: y
   y%a = [1,2]
   call s((y))
   if (any (y%a .ne. [3,4])) stop 1
contains
   subroutine s(x)
  class(*) :: x
  select type (x)
type is (t)
  x%a = x%a + 2
class default
  stop 2
  end select
   end
end
! { dg-do run }
module m
   type t
  real :: r
   contains
  procedure :: op
  procedure :: assign
  generic :: operator(*) => op
  generic :: assignment(=) => assign
   end type
contains
   function op (x, y)
  class(t), allocatable :: op
  class(t), intent(in) :: x
  real, intent(in) :: y
  allocate (op, source = t (x%r * y))
   end
   subroutine assign (z, x)
  type(t), intent(in) :: x
  class(t), intent(out) :: z
  z%r = x%r
   end
end
program p
   use m
   class(t), allocatable :: x
   real :: y = 2
   allocate (x, source = t (2.0))
   x = x * y
   if (int (x%r) .ne. 4) stop 1
   if (allocated (x)) deallocate (x)
end
! { dg-do run }
!
! Contributed by Steve Kargl  
!
program main
   implicit none
   type stuff
  character(:), allocatable :: key
   end type stuff
   type(stuff) nonsense, total
   nonsense = stuff('Xe')
   total = stuff(nonsense%key) ! trim nonsense%key made this work
   if (nonsense%key /= total%key) call abort
   if (len(total%key) /= 2) call abort
end program main


Change.Logs
Description: Binary data
diff --git a/gcc/fortran/interface.cc b/gcc/fortran/interface.cc
index e9843e9549c..fa505ab7ed9 100644
--- a/gcc/fortran/interface.cc
+++ b/gcc/fortran/interface.cc
@@ -3312,6 +3312,16 @@ gfc_compare_actual_formal (gfc_actual_arglist **ap, gfc_formal_arglist *formal,
 	}
 	}
 
+  if (UNLIMITED_POLY (a->expr)
+	  && !(f->sym->ts.type == BT_ASSUMED || UNLIMITED_POLY (f->sym)))
+	{
+	  gfc_error ("Unlim

Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Mikael Morin

Hello,

Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :

Dear all,

Fortran 2018 added a clarification that the *result* of a function
whose result *variable* has the ALLOCATABLE attribute is a *value*
that itself does not have the ALLOCATABLE attribute.

For those interested: there was a thread on the J3 mailing list
some time ago (for links see the PR).

The patch which implements a related check was co-authored with
Steve and regtested by him.  Testcase verified against NAG.

OK for mainline (gcc-14)?

Looks good in principle, but I think the real fix should be in the 
gfc_expr_attr function, which copies all the attributes (including 
allocatable) in the EXPR_FUNCTION case.  How would the testsuite react 
if that attribute was cleared there?  Is your patch still needed if 
gfc_expr_attr is fixed?


Mikael


Re: coarrays using extended precision (80 bits) ?

2023-04-22 Thread Jorge D'Elia via Fortran
Dear Steve,

- Mensaje original -
> De: "Gfortran List" org>
> Para: "Jorge D'Elia" conicet.gov.ar>
> CC: "Gfortran List" org>
> Enviado: Viernes, 21 de Abril 2023 19:53:26
> Asunto: Re: coarrays using extended precision (80 bits) ?
>
> On Fri, Apr 21, 2023 at 08:33:31AM -0300, Jorge D'Elia wrote:
>> Dear GFortran developers,
>> 
>> One question: is there any chance of encoding with coarrays using
>> extended precision (80 bits) at least inside a multicore computer?
>> (as if to simplify a bit).
>> 
>> To date, the possibility of using double precision (64 bits) or
>> extended precision (80 bits) is an alternative in our production
>> code, but sometimes we would like to do computations in
>> 80 bits and, in certain parts, there are coarrays.
>> We have validated even in quadruple precision (128 bits), using
>> ifort although, as is well known, the CPU times are largely
>> excessive.
>> 
>> Thanks in any case.
>> 
> 
> Well, I just installed OpenCoarray and downloaded a pi/4
> monte carlo code that Thomas wrote using REAL.  I changed
> everything to use REAL(10).  Compiled and executed without
> a problem.  I also tested REAL(16), which worked although
> it's painfully slow due to software floating point.  So,
> I guess I don't understand what you're asking?
> 
> --
> Steve

Thanks a lot for your answer. Now:

Since we were noticing numerical issues in certain cases in our code, 
we moved on to a toy model. The toy model is based on a standard LU 
factorization with a dense block-distributed system matrix. So:

1/2) When we use gfortran+opencoarrays:
The verification computation of the numerical solution of the system 
of equations is OK if we use precision either (single, double, extended, 
quadruple) when the number Z of images is equal to 1. It is also OK if 
we use precision either (single, double) when Z>1. But it fails if we 
use precision either (extended, quadruple) when Z>1.

2/2) When we use ifort:
The verification computation of the numerical solution of the system 
of equations is OK if we use precision either (single, double, quadruple) 
either when Z=1 or when Z>1. We cannot check it in extended precision 
because ifort does not support the use of extended precision.

As a first attempt to explain the discrepancy, we assume that those 
verification failures in the solution could be attributed to 
gfortran+opencoarrays not quite correctly transmitting numbers in 
extended precision, because opencoarrays relies on some standard MPI 
for single and double precision (it would be like this?).

Best regards.
Jorge.
--
CIMEC (UNL-CONICET), cimec.conicet.gov.ar, www.cimec.org.ar


Re: coarrays using extended precision (80 bits) ?

2023-04-22 Thread Steve Kargl via Fortran
On Sat, Apr 22, 2023 at 07:46:12AM -0300, Jorge D'Elia wrote:
> > On Fri, Apr 21, 2023 at 08:33:31AM -0300, Jorge D'Elia wrote:
> >> 
> >> One question: is there any chance of encoding with coarrays using
> >> extended precision (80 bits) at least inside a multicore computer?
> >> (as if to simplify a bit).
> >> 
> >> To date, the possibility of using double precision (64 bits) or
> >> extended precision (80 bits) is an alternative in our production
> >> code, but sometimes we would like to do computations in
> >> 80 bits and, in certain parts, there are coarrays.
> >> We have validated even in quadruple precision (128 bits), using
> >> ifort although, as is well known, the CPU times are largely
> >> excessive.
> >> 
> > Well, I just installed OpenCoarray and downloaded a pi/4
> > monte carlo code that Thomas wrote using REAL.  I changed
> > everything to use REAL(10).  Compiled and executed without
> > a problem.  I also tested REAL(16), which worked although
> > it's painfully slow due to software floating point.  So,
> > I guess I don't understand what you're asking?
> > 
> 
> Thanks a lot for your answer. Now:
> 
> Since we were noticing numerical issues in certain cases in our code, 
> we moved on to a toy model. The toy model is based on a standard LU 
> factorization with a dense block-distributed system matrix. So:
> 
> 1/2) When we use gfortran+opencoarrays:
> The verification computation of the numerical solution of the system 
> of equations is OK if we use precision either (single, double, extended, 
> quadruple) when the number Z of images is equal to 1. It is also OK if 
> we use precision either (single, double) when Z>1. But it fails if we 
> use precision either (extended, quadruple) when Z>1.
> 
> 2/2) When we use ifort:
> The verification computation of the numerical solution of the system 
> of equations is OK if we use precision either (single, double, quadruple) 
> either when Z=1 or when Z>1. We cannot check it in extended precision 
> because ifort does not support the use of extended precision.
> 
> As a first attempt to explain the discrepancy, we assume that those 
> verification failures in the solution could be attributed to 
> gfortran+opencoarrays not quite correctly transmitting numbers in 
> extended precision, because opencoarrays relies on some standard MPI 
> for single and double precision (it would be like this?).

This might be a bug in OC or gfortran or both.  It is unclear if
there is any further work being done on OC.  If the LU toy code
is short enough, you might try compiling it with -fcoarray=lib
-fdump-tree-original to see if there are any obvious function
argument mismatches in the underlying code.

I looked more closely at Thomas's code.  It was passing
integer arrays between images while the images internally
used REAL(10).  If it's an argument passing issues with
REAL(10), his code would not expose it.

-- 
Steve


Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Steve Kargl via Fortran
On Sat, Apr 22, 2023 at 11:25:41AM +0200, Mikael Morin wrote:
> 
> Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :
> > Dear all,
> > 
> > Fortran 2018 added a clarification that the *result* of a function
> > whose result *variable* has the ALLOCATABLE attribute is a *value*
> > that itself does not have the ALLOCATABLE attribute.
> > 
> > For those interested: there was a thread on the J3 mailing list
> > some time ago (for links see the PR).
> > 
> > The patch which implements a related check was co-authored with
> > Steve and regtested by him.  Testcase verified against NAG.
> > 
> > OK for mainline (gcc-14)?
> > 
> Looks good in principle, but I think the real fix should be in the
> gfc_expr_attr function, which copies all the attributes (including
> allocatable) in the EXPR_FUNCTION case.  How would the testsuite react if
> that attribute was cleared there?  Is your patch still needed if
> gfc_expr_attr is fixed?

You may be correct that something can be done elsewhere.
I do note that a function result can be allocatable
(within the funciton body).  The issue only arises when
argument association is done, which is done where Harald
and I have the patch.  Do we know that the function will
be an actual argument associated with an allocatable 
dummy argument when gfc_expr_attr is invoked?

-- 
Steve


Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Mikael Morin

Le 22/04/2023 à 15:52, Steve Kargl a écrit :

On Sat, Apr 22, 2023 at 11:25:41AM +0200, Mikael Morin wrote:


Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :

Dear all,

Fortran 2018 added a clarification that the *result* of a function
whose result *variable* has the ALLOCATABLE attribute is a *value*
that itself does not have the ALLOCATABLE attribute.

For those interested: there was a thread on the J3 mailing list
some time ago (for links see the PR).

The patch which implements a related check was co-authored with
Steve and regtested by him.  Testcase verified against NAG.

OK for mainline (gcc-14)?


Looks good in principle, but I think the real fix should be in the
gfc_expr_attr function, which copies all the attributes (including
allocatable) in the EXPR_FUNCTION case.  How would the testsuite react if
that attribute was cleared there?  Is your patch still needed if
gfc_expr_attr is fixed?


You may be correct that something can be done elsewhere.
I do note that a function result can be allocatable
(within the funciton body).  The issue only arises when
argument association is done, which is done where Harald
and I have the patch.  Do we know that the function will
be an actual argument associated with an allocatable
dummy argument when gfc_expr_attr is invoked?

No, there is no context information in gfc_expr_attr, but the result 
should not be dependent on context anyway.


You are probably right that the impact of this bug is limited to the 
case of argument association, not as broad as I thought.  Yet we should 
not keep gfc_expr_attr returning an allocatable attribute for function 
expressions in any case.


Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Steve Kargl via Fortran
On Sat, Apr 22, 2023 at 05:17:30PM +0200, Mikael Morin wrote:
> Le 22/04/2023 à 15:52, Steve Kargl a écrit :
> > On Sat, Apr 22, 2023 at 11:25:41AM +0200, Mikael Morin wrote:
> > > 
> > > Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :
> > > > Dear all,
> > > > 
> > > > Fortran 2018 added a clarification that the *result* of a function
> > > > whose result *variable* has the ALLOCATABLE attribute is a *value*
> > > > that itself does not have the ALLOCATABLE attribute.
> > > > 
> > > > For those interested: there was a thread on the J3 mailing list
> > > > some time ago (for links see the PR).
> > > > 
> > > > The patch which implements a related check was co-authored with
> > > > Steve and regtested by him.  Testcase verified against NAG.
> > > > 
> > > > OK for mainline (gcc-14)?
> > > > 
> > > Looks good in principle, but I think the real fix should be in the
> > > gfc_expr_attr function, which copies all the attributes (including
> > > allocatable) in the EXPR_FUNCTION case.  How would the testsuite react if
> > > that attribute was cleared there?  Is your patch still needed if
> > > gfc_expr_attr is fixed?
> > 
> > You may be correct that something can be done elsewhere.
> > I do note that a function result can be allocatable
> > (within the funciton body).  The issue only arises when
> > argument association is done, which is done where Harald
> > and I have the patch.  Do we know that the function will
> > be an actual argument associated with an allocatable
> > dummy argument when gfc_expr_attr is invoked?
> > 
> No, there is no context information in gfc_expr_attr, but the result should
> not be dependent on context anyway.
> 
> You are probably right that the impact of this bug is limited to the case of
> argument association, not as broad as I thought.  Yet we should not keep
> gfc_expr_attr returning an allocatable attribute for function expressions in
> any case.

I suspect we're stuck in a catch-22 situation.  The symbol is
marked as allocatable,

function foo()
   integer, allocatable :: foo
   foo = 42   !<--- So that this isn't rejected
end

but when the function is actually referenced in an expression
the result is normally used, and symbol is still marked as
allocatable.

-- 
Steve


Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Harald Anlauf via Fortran

Hi Mikael,

Am 22.04.23 um 11:25 schrieb Mikael Morin:

Hello,

Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :

Dear all,

Fortran 2018 added a clarification that the *result* of a function
whose result *variable* has the ALLOCATABLE attribute is a *value*
that itself does not have the ALLOCATABLE attribute.

For those interested: there was a thread on the J3 mailing list
some time ago (for links see the PR).

The patch which implements a related check was co-authored with
Steve and regtested by him.  Testcase verified against NAG.

OK for mainline (gcc-14)?


Looks good in principle, but I think the real fix should be in the
gfc_expr_attr function, which copies all the attributes (including
allocatable) in the EXPR_FUNCTION case.  How would the testsuite react
if that attribute was cleared there?  Is your patch still needed if
gfc_expr_attr is fixed?


you mean like the following?

diff --git a/gcc/fortran/primary.cc b/gcc/fortran/primary.cc
index 00d35a71770..7517efc5414 100644
--- a/gcc/fortran/primary.cc
+++ b/gcc/fortran/primary.cc
@@ -2775,6 +2775,7 @@ gfc_expr_attr (gfc_expr *e)
  attr.pointer = CLASS_DATA (sym)->attr.class_pointer;
  attr.allocatable = CLASS_DATA (sym)->attr.allocatable;
}
+ attr.allocatable = 0;
}
   else if (e->value.function.isym
   && e->value.function.isym->transformational

While this leads to a rejection of the testcase, I see regressions
e.g. on allocatable_function_1.f90 and allocatable_function_8.f90
because the function result from a previous invocation does not get
freed, and on a subsequent function reference the result variable
should always be unallocated.

Not sure if the "catch-22" Steve mentions is a good characterization,
but a function reference with assignment of the result to an
(allocatable) variable, like

  integer, allocatable  :: p
  p = f()

is semantically different from an ordinary assignment to an
allocatable variable, where the r.h.s. is an allocatable variable,
because the function result variable *must* be deallocated after
the assignment, whereas an ordinary variable on the r.h.s must
remain unaltered.

So I guess it is much less risky to approach the issue by not
allowing argument association to an allocatable dummy for an
actual argument that is a function reference.  (I initially had
an even stricter idea to allow only an allocatable *variable*
for the actual argument, but did not check the lengthy text
on argument association).


Mikael



Harald



Re: [PATCH] Fortran: function results never have the ALLOCATABLE attribute [PR109500]

2023-04-22 Thread Mikael Morin

Le 22/04/2023 à 20:19, Harald Anlauf a écrit :

Hi Mikael,

Am 22.04.23 um 11:25 schrieb Mikael Morin:

Hello,

Le 20/04/2023 à 22:01, Harald Anlauf via Fortran a écrit :

Dear all,

Fortran 2018 added a clarification that the *result* of a function
whose result *variable* has the ALLOCATABLE attribute is a *value*
that itself does not have the ALLOCATABLE attribute.

For those interested: there was a thread on the J3 mailing list
some time ago (for links see the PR).

The patch which implements a related check was co-authored with
Steve and regtested by him.  Testcase verified against NAG.

OK for mainline (gcc-14)?


Looks good in principle, but I think the real fix should be in the
gfc_expr_attr function, which copies all the attributes (including
allocatable) in the EXPR_FUNCTION case.  How would the testsuite react
if that attribute was cleared there?  Is your patch still needed if
gfc_expr_attr is fixed?


you mean like the following?

diff --git a/gcc/fortran/primary.cc b/gcc/fortran/primary.cc
index 00d35a71770..7517efc5414 100644
--- a/gcc/fortran/primary.cc
+++ b/gcc/fortran/primary.cc
@@ -2775,6 +2775,7 @@ gfc_expr_attr (gfc_expr *e)
   attr.pointer = CLASS_DATA (sym)->attr.class_pointer;
   attr.allocatable = CLASS_DATA (sym)->attr.allocatable;
     }
+ attr.allocatable = 0;
     }
    else if (e->value.function.isym
    && e->value.function.isym->transformational


Yes, like this.


While this leads to a rejection of the testcase, I see regressions
e.g. on allocatable_function_1.f90 and allocatable_function_8.f90
because the function result from a previous invocation does not get
freed, and on a subsequent function reference the result variable
should always be unallocated.


Meh!


Not sure if the "catch-22" Steve mentions is a good characterization,
but a function reference with assignment of the result to an
(allocatable) variable, like

   integer, allocatable  :: p
   p = f()

is semantically different from an ordinary assignment to an
allocatable variable, where the r.h.s. is an allocatable variable,
because the function result variable *must* be deallocated after
the assignment, whereas an ordinary variable on the r.h.s must
remain unaltered.

So I guess it is much less risky to approach the issue by not
allowing argument association to an allocatable dummy for an
actual argument that is a function reference.  (I initially had
an even stricter idea to allow only an allocatable *variable*
for the actual argument, but did not check the lengthy text
on argument association).


OK, let's go with your patch as originally submitted then.

Thanks.