Re: Fw: Re: [Patch, fortran] PR37336 (Finalization) - [F03] Finish derived-type finalization

2023-01-07 Thread Paul Richard Thomas via Fortran
Hi All,

Please find attached a patch for trans-array.cc that does what Harald
suggests; ie. finalization of array and structure constructors only occurs
with -std=f2003/8. Two versions of finalize_38.f90 are attached. One which
tests -std=gnu/f20018 and the other -std=f2008.

Frankly, I think that this is better. Finalization of these expressions
must be handled with a lot of care and was deleted by f2018 for good
reasons. Above all else, the results do not represent defined entities and
so it does not really make sense to finalize them. My vote is to go with
this version of the patch.

I am struggling a bit with a nit in finalize_45. One of the other
processors appears to nullify the pointer component of the result
of construct_t during finalization of the result. I can see the sense in
this but do not find any requirement to do so in the standard.

Given the scale of the overall patch, I am beginning to have a lot of
sympathy with Thomas's suggestion that the finalization calls should be
moved to the front end! I will take a quick look to see how easy this would
be to implement.

Regards

Paul


On Fri, 6 Jan 2023 at 08:34, Harald Anlauf via Fortran 
wrote:

> Hi Jerry,
>
> > Gesendet: Freitag, 06. Januar 2023 um 04:08 Uhr
> > Von: "Jerry D" 
> > An: "Harald Anlauf" , "fortran" 
> > Betreff: Re: Fw: Re: [Patch, fortran] PR37336 (Finalization) - [F03]
> Finish derived-type finalization
> >
> > On 1/5/23 1:14 PM, Harald Anlauf via Fortran wrote:
> > > Resending as plain text, as the original version did not appear on the
> fortran list...
> > >
> > >
> > > Gesendet: Donnerstag, 05. Januar 2023 um 22:10 Uhr
> > > Von: "Harald Anlauf" 
> > > An: "Paul Richard Thomas" 
> > > Cc: "fortran@gcc.gnu.org" , "Alessandro
> Fanfarillo" , "Andrew Benson" <
> aben...@carnegiescience.edu>, "Thomas Koenig" ,
> "Damian Rouson" 
> > > Betreff: Re: [Patch, fortran] PR37336 (Finalization) - [F03] Finish
> derived-type finalization
> > >
> > > Dear Paul, all,
> > >
> > > I had a first look at the patch and the testcases, and I really look
> forward to getting this into gfortran.
> > >
> > > A few questions surfaced when playing with it, which is why am asking
> for others to comment.
> > >
> > > Testcase finalize_38.f90 exhibits a (potential) discrepancy to my
> expections when playing with options -std=f2018 and -std=gnu (the default).
> > >
> > > What is the expected behavior of -std=gnu?  My expectation is that
> -std=gnu always corresponds to the latest implemented standard (currently
> F2018), except for possibly allowing for GNU-extensions.  This might imply
> that corrigenda to a standard or a newer version may lead (over time) to an
> adjustment of the behavior.  Any opinions on it?  Do we need to always test
> (in the testsuite) for compliance with older standards?
> > >
> >
> > My understanding is that -std=gnu tends to be the least restrictive and
> > will allow finalize_38.f90 to compile possibly with warnings. The
> > warnings are to allow the user to know thay are out of current
> > compliance, but we should not fail on code that was previously compliant
> > and less we specify -std=f2018 which is more restrictive.
>
> So if e.g. finalize_38.f90 compiles without warnings with -std=f2018,
> it should also compile without warnings with -std=gnu, right?
>
> Harald
>
>
> > Jerry
> >
> >
>


-- 
"If you can't explain it simply, you don't understand it well enough" -
Albert Einstein
! { dg-do run }
!
! Test finalization on intrinsic assignment (F2018 (7.5.6.3))
! With -std=gnu, no finalization of array or structure constructors should occur.
! See finalize_38a.f90 for the result with f2008.
! Tests fix for PR64290 as well.
!
module testmode
  implicit none

  type :: simple
integer :: ind
  contains
final :: destructor1, destructor2
  end type simple

  type, extends(simple) :: complicated
real :: rind
  contains
final :: destructor3, destructor4
  end type complicated

  integer :: check_scalar
  integer :: check_array(4)
  real :: check_real
  real :: check_rarray(4)
  integer :: final_count = 0

contains

  subroutine destructor1(self)
type(simple), intent(inout) :: self
check_scalar = self%ind
check_array = 0
final_count = final_count + 1
  end subroutine destructor1

  subroutine destructor2(self)
type(simple), intent(inout) :: self(:)
check_scalar = 0
check_array(1:size(self, 1)) = self%ind
final_count = final_count + 1
  end subroutine destructor2

  subroutine destructor3(self)
type(complicated), intent(inout) :: self
check_real = self%rind
check_array = 0.0
final_count = final_count + 1
  end subroutine destructor3

  subroutine destructor4(self)
type(complicated), intent(inout) :: self(:)
check_real = 0.0
check_rarray(1:size(self, 1)) = self%rind
final_count = final_count + 1
  end subroutine destructor4

  function constructor1(ind) result(res)
class(simple), allocatable :: res
integer, intent(in) :: ind
allocate (r

Re: Fw: Re: [Patch, fortran] PR37336 (Finalization) - [F03] Finish derived-type finalization

2023-01-07 Thread Thomas Koenig via Fortran

Hi Paul,

first, thanks for taking on this rather monumental task!


Given the scale of the overall patch, I am beginning to have a lot of
sympathy with Thomas's suggestion that the finalization calls should be
moved to the front end! I will take a quick look to see how easy this would
be to implement.


There is one drawback if you do this in the front end:  There are a few
places where it is not possible to add code without running into ICEs
later, like WHERE/ELSEWHERE, which is why fronend_passes.cc keeps track
of these things.

Best regards

Thomas


[patch, fortran] Fix common subexpression elimination with IEEE rounding (PR108329)

2023-01-07 Thread Thomas Koenig via Fortran

Hello world,

this patch fixes Fortran's handling of common subexpression elimination
across ieee_set_rouding_mode calls.  It does so using a rather big
hammer, by issuing a memory barrier to force reload from memory
(and thus a recomputation).

This is a rather big hammer, so if there are more elegant ways
to fix it, I am very much open to suggestions.

If PR 34678 is fixed, then this solution can also be applied here.

OK for trunk?  How do you feel about a backport?

Best regards

Thomas

Add memory barrier for calls to ieee_set_rounding_mode.

gcc/fortran/ChangeLog:

PR fortran/108329
* trans-expr.cc (trans_memory_barrier): New functions.
(gfc_conv_procedure_call): Insert memory barrier for
ieee_set_rounding_mode.

gcc/testsuite/ChangeLog:

PR fortran/108329
* gfortran.dg/rounding_4.f90: New test.diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 4f3ae82d39c..29be7804e11 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -5981,6 +5981,20 @@ post_call:
 gfc_add_block_to_block (&parmse->post, &block);
 }
 
+/* Helper function - generate a memory barrier.  */
+
+static tree
+trans_memory_barrier (void)
+{
+  tree tmp;
+
+  tmp = gfc_build_string_const (sizeof ("memory"), "memory");
+  tmp = build5_loc (input_location, ASM_EXPR, void_type_node,
+		gfc_build_string_const (1, ""), NULL_TREE, NULL_TREE,
+		tree_cons (NULL_TREE, tmp, NULL_TREE), NULL_TREE);
+  ASM_VOLATILE_P (tmp) = 1;
+  return tmp;
+}
 
 /* Generate code for a procedure call.  Note can return se->post != NULL.
If se->direct_byref is set then se->expr contains the return parameter.
@@ -7692,6 +7706,19 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
   else
 conv_base_obj_fcn_val (se, base_object, expr);
 
+  /* FIXME: Special handing of ieee_set_rounding_mode - we clobber
+ memory here to avoid common subexpression moving code past calls
+ to ieee_set_rounding_mode.  This should only be done for
+ floating point, but currently gcc offers no other possibility.
+ See PR 108329.  */
+
+  if (sym->from_intmod == INTMOD_IEEE_ARITHMETIC
+  && strcmp (sym->name, "ieee_set_rounding_mode") == 0)
+{
+  tree tmp = trans_memory_barrier ();
+  gfc_add_expr_to_block (&post, tmp);
+}
+
   /* If there are alternate return labels, function type should be
  integer.  Can't modify the type in place though, since it can be shared
  with other functions.  For dummy arguments, the typing is done to
diff --git a/gcc/testsuite/gfortran.dg/rounding_4.f90 b/gcc/testsuite/gfortran.dg/rounding_4.f90
new file mode 100644
index 000..e8799da67dc
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/rounding_4.f90
@@ -0,0 +1,31 @@
+! { dg-do run }
+module y
+  implicit none
+  integer, parameter :: wp = selected_real_kind(15)
+contains
+  subroutine foo(a,b,c)
+use ieee_arithmetic
+real(kind=wp), dimension(4), intent(out) :: a
+real(kind=wp), intent(in) :: b, c
+type (ieee_round_type), dimension(4), parameter :: mode = &
+ [ieee_nearest, ieee_to_zero, ieee_up, ieee_down]
+call ieee_set_rounding_mode (mode(1))
+a(1) = b + c
+call ieee_set_rounding_mode (mode(2))
+a(2) = b + c
+call ieee_set_rounding_mode (mode(3))
+a(3) = b + c
+call ieee_set_rounding_mode (mode(4))
+a(4) = b + c
+  end subroutine foo
+end module y
+
+program main
+  use y
+  real(kind=wp), dimension(4) :: a
+  call foo(a,0.1_wp,0.2_wp)
+  if (a(1) <= a(2)) stop 1
+  if (a(3) <= a(4)) stop 2
+  if (a(1) /= a(3)) stop 3
+  if (a(2) /= a(4)) stop 4
+end program main


Re: Fw: Re: [Patch, fortran] PR37336 (Finalization) - [F03] Finish derived-type finalization

2023-01-07 Thread Paul Richard Thomas via Fortran
Hi Thomas,

What causes the ICES?

Cheers

Paul


On Sat, 7 Jan 2023 at 15:28, Thomas Koenig  wrote:

> Hi Paul,
>
> first, thanks for taking on this rather monumental task!
>
> > Given the scale of the overall patch, I am beginning to have a lot of
> > sympathy with Thomas's suggestion that the finalization calls should be
> > moved to the front end! I will take a quick look to see how easy this
> would
> > be to implement.
>
> There is one drawback if you do this in the front end:  There are a few
> places where it is not possible to add code without running into ICEs
> later, like WHERE/ELSEWHERE, which is why fronend_passes.cc keeps track
> of these things.
>
> Best regards
>
> Thomas
>


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