I'm taking a leave of absence

2021-04-16 Thread Thomas Koenig via Fortran



Hell world,

I'm taking a leave of absence from gfortran for a time.

The reason is the current discussions on the gcc mailing list,
which I do not adivse you to read if you value your mental health
and healthy blood pressure :-|

I have unassigned all bugs assigned to me and set them to NEW.

Best regards

Thomas


Patch, fortran] PR fortran/100120 - associated intrinsic failure

2021-04-16 Thread José Rui Faustino de Sousa via Fortran

Hi All!

Proposed patch to:

PR100120 - associated intrinsic failure

Patch tested only on x86_64-pc-linux-gnu.

Add code to ensure that pointers have the correct dynamic type.

The patch depends on PR100097 and PR100098.

Thank you very much.

Best regards,
José Rui

Fortran: Fix associated intrinsic failure [PR100120]

gcc/fortran/ChangeLog:

PR fortran/100120
* trans-array.c (gfc_conv_expr_descriptor): add code to ensure
that pointers have the correct dynamic type.

gcc/testsuite/ChangeLog:

PR fortran/100120
* gfortran.dg/PR100120.f90: New test.

diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index ca90142530c..0ef6c788465 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -7598,6 +7598,7 @@ gfc_conv_expr_descriptor (gfc_se *se, gfc_expr *expr)
   int dim, ndim, codim;
   tree parm;
   tree parmtype;
+  tree dtype;
   tree stride;
   tree from;
   tree to;
@@ -7670,24 +7671,24 @@ gfc_conv_expr_descriptor (gfc_se *se, gfc_expr *expr)
 	  loop.from[dim] = gfc_index_one_node;
 	}
 
+  /* The destination must carry the dynamic type of the expression...  */
   desc = info->descriptor;
+  if (expr->ts.type == BT_CHARACTER && expr->ts.deferred)
+	parmtype = gfc_typenode_for_spec (>ts);
+  else
+	parmtype = gfc_get_element_type (TREE_TYPE (desc));
+
+  /* ...But the destination has it's own rank and shape.  */
+  parmtype = gfc_get_array_type_bounds (parmtype, loop.dimen, codim,
+	loop.from, loop.to, 0,
+	GFC_ARRAY_UNKNOWN, false);
+
   if (se->direct_byref && !se->byref_noassign)
-	{
-	  /* For pointer assignments we fill in the destination.  */
-	  parm = se->expr;
-	  parmtype = TREE_TYPE (parm);
-	}
+	/* For pointer assignments we fill in the destination.  */
+	parm = se->expr;
   else
 	{
 	  /* Otherwise make a new one.  */
-	  if (expr->ts.type == BT_CHARACTER && expr->ts.deferred)
-	parmtype = gfc_typenode_for_spec (>ts);
-	  else
-	parmtype = gfc_get_element_type (TREE_TYPE (desc));
-
-	  parmtype = gfc_get_array_type_bounds (parmtype, loop.dimen, codim,
-		loop.from, loop.to, 0,
-		GFC_ARRAY_UNKNOWN, false);
 	  parm = gfc_create_var (parmtype, "parm");
 
 	  /* When expression is a class object, then add the class' handle to
@@ -7731,8 +7732,18 @@ gfc_conv_expr_descriptor (gfc_se *se, gfc_expr *expr)
  the offsets because all elements are within the array data.  */
 
   /* Set the dtype.  */
+  if (expr->expr_type == EXPR_VARIABLE
+	  && expr->symtree->n.sym->attr.dummy
+	  && IS_CLASS_ARRAY (expr->symtree->n.sym))
+	{
+	  tmp = gfc_get_class_from_gfc_expr (expr);
+	  tmp = gfc_class_data_get (tmp);
+	  dtype = gfc_conv_descriptor_dtype (tmp);
+	}
+  else
+	dtype = gfc_get_dtype (parmtype);
   tmp = gfc_conv_descriptor_dtype (parm);
-  gfc_add_modify (, tmp, gfc_get_dtype (parmtype));
+  gfc_add_modify (, tmp, dtype);
 
   /* The 1st element in the section.  */
   base = gfc_index_zero_node;
diff --git a/gcc/testsuite/gfortran.dg/PR100120.f90 b/gcc/testsuite/gfortran.dg/PR100120.f90
new file mode 100644
index 000..58a22d72c26
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/PR100120.f90
@@ -0,0 +1,166 @@
+! { dg-do run }
+!
+! Tests fix for PR100120
+!
+
+program main_p
+
+  implicit none
+
+  integer, parameter :: n = 11
+
+  type :: foo_t
+integer :: i
+  end type foo_t
+
+  type, extends(foo_t) :: bar_t
+integer :: j(n)
+  end type bar_t
+  
+  class(*), pointer :: spu
+  class(*), pointer :: apu(:)
+  class(foo_t), pointer :: spf
+  class(foo_t), pointer :: apf(:)
+  class(bar_t), pointer :: spb
+  class(bar_t), pointer :: apb(:)
+  type(foo_t),   target :: afd(n)
+  type(bar_t),   target :: abd(n)
+  integer,   target :: ain(n)
+  integer   :: i
+
+  ain = [(i, i=1,n)]
+  afd%i = ain
+  abd%i = ain
+  do i = 1, n
+abd(i)%j = ain
+  end do
+
+  apu => ain
+  if(.not.associated(apu)) stop 1
+  if(.not.associated(apu, ain)) stop 2
+  select type(apu)
+  type is(integer)
+if(any(apu/=ain)) stop 3
+  class default
+stop 4
+  end select
+  spu => ain(n)
+  if(.not.associated(spu)) stop 5
+  if(.not.associated(spu, ain(n))) stop 6
+  select type(spu)
+  type is(integer)
+if(spu/=n) stop 7
+  class default
+stop 8
+  end select
+
+  apu => afd
+  if(.not.associated(apu)) stop 10
+  if(.not.associated(apu, afd)) stop 11
+  select type(apu)
+  type is(foo_t)
+if(any(apu%i/=afd%i)) stop 12
+  class default
+stop 13
+  end select
+  spu => afd(n)
+  if(.not.associated(spu)) stop 14
+  if(.not.associated(spu, afd(n))) stop 15
+  select type(spu)
+  type is(foo_t)
+if(spu%i/=n) stop 16
+  class default
+stop 17
+  end select
+  
+  apu => abd
+  if(.not.associated(apu)) stop 20
+  if(.not.associated(apu, abd)) stop 21
+  select type(apu)
+  type is(bar_t)
+if(any(apu%i/=abd%i)) stop 22
+do i = 1, n
+  

Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Harald Anlauf via Fortran
Hi Paul, all,
 
having really enjoyed the review process, I've now committed Paul's version
including his comment.  See also attached.

Thanks,
Harald

 
Gesendet: Freitag, 16. April 2021 um 13:02 Uhr
Von: "Paul Richard Thomas" 
An: "Bernhard Reutner-Fischer" 
Cc: "Harald Anlauf via Fortran" , "Harald Anlauf" 

Betreff: Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

Hi Harald,
 
This is the output from a completely tedious Zoom meeting:
 
  /* From F2003 onwards, intrinsic procedures are no longer subject to
     the restriction, "that an elemental intrinsic function here be of
     type integer or character and each argument must be an initialization
     expr of type integer or character" is lifted so that intrinsic
     procedures can be over-ridden. This requires that the intrinsic
     symbol not appear in the module file, thereby preventing ambiguity
     when USEd.  */
  if (strcmp (sym->module, "(intrinsic)") == 0
      && (gfc_option.allow_std & GFC_STD_F2003))
    return;
 
Modify or replace the comment, as desired. The change to the condition gives 
the desired result in terms of standard compliance.
 
Regards
 
Paul


PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

The interface of an intrinsic procedure is automatically explicit.
Do not write it to the module file to prevent wrong ambiguities on USE.

gcc/fortran/ChangeLog:

PR fortran/63797
* module.c (write_symtree): Do not write interface of intrinsic
procedure to module file for F2003 and newer.

gcc/testsuite/ChangeLog:

PR fortran/63797
* gfortran.dg/pr63797.f90: New test.

Co-authored-by: Paul Thomas 

diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index 4db0a3ac76d..089453caa03 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -6218,6 +6218,17 @@ write_symtree (gfc_symtree *st)
   if (check_unique_name (st->name))
 return;

+  /* From F2003 onwards, intrinsic procedures are no longer subject to
+ the restriction, "that an elemental intrinsic function here be of
+ type integer or character and each argument must be an initialization
+ expr of type integer or character" is lifted so that intrinsic
+ procedures can be over-ridden. This requires that the intrinsic
+ symbol not appear in the module file, thereby preventing ambiguity
+ when USEd.  */
+  if (strcmp (sym->module, "(intrinsic)") == 0
+  && (gfc_option.allow_std & GFC_STD_F2003))
+return;
+
   p = find_pointer (sym);
   if (p == NULL)
 gfc_internal_error ("write_symtree(): Symbol not written");
diff --git a/gcc/testsuite/gfortran.dg/pr63797.f90 b/gcc/testsuite/gfortran.dg/pr63797.f90
new file mode 100644
index 000..1131e8167b1
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/pr63797.f90
@@ -0,0 +1,60 @@
+! { dg-do compile }
+! PR63797 - Bogus ambiguous reference to 'sqrt'
+
+module mod1
+  implicit none
+  real, parameter :: z = sqrt (0.0)
+  real:: w = sqrt (1.0)
+  interface
+ pure real function sqrt_ifc (x)
+   real, intent(in) :: x
+ end function sqrt_ifc
+  end interface
+contains
+  pure function myroot () result (f)
+procedure(sqrt_ifc), pointer :: f
+intrinsic :: sqrt
+f => sqrt
+  end function myroot
+end module mod1
+
+module mod2
+  implicit none
+  type t
+ real :: a = 0.
+  end type
+  interface sqrt
+ module procedure sqrt
+  end interface
+contains
+  elemental function sqrt (a)
+type(t), intent(in) :: a
+type(t) :: sqrt
+sqrt% a = a% a
+  end function sqrt
+end module mod2
+
+module mod3
+  implicit none
+  abstract interface
+ function real_func (x)
+   real  :: real_func
+   real, intent (in) :: x
+ end function real_func
+  end interface
+  intrinsic :: sqrt
+  procedure(real_func), pointer :: real_root => sqrt
+end module mod3
+
+program test
+  use mod1
+  use mod2
+  use mod3
+  implicit none
+  type(t) :: x, y
+  procedure(sqrt_ifc), pointer :: root
+  root => myroot ()
+  y= sqrt (x)
+  y% a = sqrt (x% a) + z - w + root (x% a)
+  y% a = real_root (x% a)
+end program test


Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Paul Richard Thomas via Fortran
Hi Harald,

This is the output from a completely tedious Zoom meeting:

  /* From F2003 onwards, intrinsic procedures are no longer subject to
 the restriction, "that an elemental intrinsic function here be of
 type integer or character and each argument must be an initialization
 expr of type integer or character" is lifted so that intrinsic
 procedures can be over-ridden. This requires that the intrinsic
 symbol not appear in the module file, thereby preventing ambiguity
 when USEd.  */
  if (strcmp (sym->module, "(intrinsic)") == 0
  && (gfc_option.allow_std & GFC_STD_F2003))
return;

Modify or replace the comment, as desired. The change to the condition
gives the desired result in terms of standard compliance.

Regards

Paul


On Fri, 16 Apr 2021 at 09:32, Paul Richard Thomas <
paul.richard.tho...@gmail.com> wrote:

> Hi All,
>
> Harald, that is to say the least of it an elegant and minimalist fix. With
> the patch applied, gfortran behaves like the "other brand" and regtests OK.
>
> Bernhard correctly points out that there should be a comment. Not only
> this, there must be an F2003 standard check, since F95 forbids over-riding
> of elemental intrinsics.
>
> I see as I am writing that Tobias has dealt with the point about module
> version. I agree entirely with Tobias. The fact that the patch is
> permissive in suppressing an incorrect error means that it cannot break
> anything.
>
> This patch, once modified as above, should be pushed to master right
> immediately and, since it affects F2003 compliance, backported to 10-branch.
>
> Many thanks, Harald - good work!
>
> Paul
>
>
>
>
>
> On Fri, 16 Apr 2021 at 08:41, Bernhard Reutner-Fischer via Fortran <
> fortran@gcc.gnu.org> wrote:
>
>> On Thu, 15 Apr 2021 22:52:01 +0200
>> Harald Anlauf via Fortran  wrote:
>>
>> > Hello everybody,
>> >
>> > we currently write the interface for intrinsic procedures to module
>> > files although that should not be necessary.  (F2018:15.4.2.1 actually
>> > states that interfaces e.g. of intrinsic procedures are 'explicit'.)
>> > This lead to bogus errors due to an apparently bogus ambiguity.
>> > A simple solution is to just avoid writing that (redundant) information
>> > to the module file.
>>
>> I'd put the standard reference you cite in a comment before the check.
>>
>> Does this change the module format in an incompatible way, i.e. does
>> this require a module format version bump?
>>
>> What happens when we read an existing module that names an intrinsic?
>> Without bumping the module version, we'd run into the same issue as
>> before, don't we?
>>
>> If we did not bump the module version yet for gcc-11 then i would
>> suggest to defer the patch for gcc-12 and bump then.
>>
>> Even if we'd skip reading existing intrinsic now, we'd break interop
>> with older compiler versions if we would stop writing them without
>> bumping the module format, i think?
>>
>> > Regtested on x86_64-pc-linux-gnu.  OK for (current) mainline?
>> > Or rather wait after 11 release?
>> >
>> > Thanks,
>> > Harald
>>
>
>
> --
> "If you can't explain it simply, you don't understand it well enough" -
> Albert Einstein
>


-- 
"If you can't explain it simply, you don't understand it well enough" -
Albert Einstein


Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Paul Richard Thomas via Fortran
Hi All,

Harald, that is to say the least of it an elegant and minimalist fix. With
the patch applied, gfortran behaves like the "other brand" and regtests OK.

Bernhard correctly points out that there should be a comment. Not only
this, there must be an F2003 standard check, since F95 forbids over-riding
of elemental intrinsics.

I see as I am writing that Tobias has dealt with the point about module
version. I agree entirely with Tobias. The fact that the patch is
permissive in suppressing an incorrect error means that it cannot break
anything.

This patch, once modified as above, should be pushed to master right
immediately and, since it affects F2003 compliance, backported to 10-branch.

Many thanks, Harald - good work!

Paul





On Fri, 16 Apr 2021 at 08:41, Bernhard Reutner-Fischer via Fortran <
fortran@gcc.gnu.org> wrote:

> On Thu, 15 Apr 2021 22:52:01 +0200
> Harald Anlauf via Fortran  wrote:
>
> > Hello everybody,
> >
> > we currently write the interface for intrinsic procedures to module
> > files although that should not be necessary.  (F2018:15.4.2.1 actually
> > states that interfaces e.g. of intrinsic procedures are 'explicit'.)
> > This lead to bogus errors due to an apparently bogus ambiguity.
> > A simple solution is to just avoid writing that (redundant) information
> > to the module file.
>
> I'd put the standard reference you cite in a comment before the check.
>
> Does this change the module format in an incompatible way, i.e. does
> this require a module format version bump?
>
> What happens when we read an existing module that names an intrinsic?
> Without bumping the module version, we'd run into the same issue as
> before, don't we?
>
> If we did not bump the module version yet for gcc-11 then i would
> suggest to defer the patch for gcc-12 and bump then.
>
> Even if we'd skip reading existing intrinsic now, we'd break interop
> with older compiler versions if we would stop writing them without
> bumping the module format, i think?
>
> > Regtested on x86_64-pc-linux-gnu.  OK for (current) mainline?
> > Or rather wait after 11 release?
> >
> > Thanks,
> > Harald
>


-- 
"If you can't explain it simply, you don't understand it well enough" -
Albert Einstein


Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Bernhard Reutner-Fischer via Fortran
On Fri, 16 Apr 2021 09:38:27 +0200
Tobias Burnus  wrote:

> On 16.04.21 09:06, Bernhard Reutner-Fischer via Fortran wrote:
> 
> > Does this change the module format in an incompatible way, i.e. does
> > this require a module format version bump?  
> Not having looked it in detail but I doubt it – it is just a symbol
> which is not output.
> > What happens when we read an existing module that names an intrinsic?
> > Without bumping the module version, we'd run into the same issue as
> > before, don't we?  
> ...
> > Even if we'd skip reading existing intrinsic now, we'd break interop
> > with older compiler versions if we would stop writing them without
> > bumping the module format, i think?  
> 
>  From the function name ("write_symtree"), gfortran only skips writing it;
> it still reads all symtrees which are in the .mod file.
> As this is the only change of Harald's patch, it should be:
> 
> * .mod by old compiler → used by new/old compiler: bogus error for 'sqrt'.
> 
> * .mod by new compiler → used by new/old compiler: works after the patch
> 
> Thus, from that side there should be no issue.

So we'd need to skip (intrinsic) when reading existing modules written
by an older compiler to fix the issue for good, as said.
But maybe that's overkill.

> And I see no point in bumping the .mod version to force the recompilation;
> those running into the corner case can still do 'make clean && make' and
> all others can keep using the old version.

That might not always be possible but admittedly that's a corner case,
yes.


Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Tobias Burnus

On 16.04.21 09:06, Bernhard Reutner-Fischer via Fortran wrote:


Does this change the module format in an incompatible way, i.e. does
this require a module format version bump?

Not having looked it in detail but I doubt it – it is just a symbol
which is not output.

What happens when we read an existing module that names an intrinsic?
Without bumping the module version, we'd run into the same issue as
before, don't we?

...

Even if we'd skip reading existing intrinsic now, we'd break interop
with older compiler versions if we would stop writing them without
bumping the module format, i think?


From the function name ("write_symtree"), gfortran only skips writing it;
it still reads all symtrees which are in the .mod file.
As this is the only change of Harald's patch, it should be:

* .mod by old compiler → used by new/old compiler: bogus error for 'sqrt'.

* .mod by new compiler → used by new/old compiler: works after the patch

Thus, from that side there should be no issue.
And I see no point in bumping the .mod version to force the recompilation;
those running into the corner case can still do 'make clean && make' and
all others can keep using the old version.

Tobias

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


Re: [PATCH] PR fortran/63797 - Bogus ambiguous reference to 'sqrt'

2021-04-16 Thread Bernhard Reutner-Fischer via Fortran
On Thu, 15 Apr 2021 22:52:01 +0200
Harald Anlauf via Fortran  wrote:

> Hello everybody,
> 
> we currently write the interface for intrinsic procedures to module
> files although that should not be necessary.  (F2018:15.4.2.1 actually
> states that interfaces e.g. of intrinsic procedures are 'explicit'.)
> This lead to bogus errors due to an apparently bogus ambiguity.
> A simple solution is to just avoid writing that (redundant) information
> to the module file.

I'd put the standard reference you cite in a comment before the check.

Does this change the module format in an incompatible way, i.e. does
this require a module format version bump?

What happens when we read an existing module that names an intrinsic?
Without bumping the module version, we'd run into the same issue as
before, don't we?

If we did not bump the module version yet for gcc-11 then i would
suggest to defer the patch for gcc-12 and bump then.

Even if we'd skip reading existing intrinsic now, we'd break interop
with older compiler versions if we would stop writing them without
bumping the module format, i think?

> Regtested on x86_64-pc-linux-gnu.  OK for (current) mainline?
> Or rather wait after 11 release?
> 
> Thanks,
> Harald