Re: [Patch, fortran] PR fortran/82376 - Duplicate function call using -fcheck=pointer

2021-04-25 Thread Paul Richard Thomas via Gcc-patches
Hi José!

The fix is fine.

Note however that the testcase will pass even without the fix because you
haven't included the
! { dg-options "-fcheck=pointer" }.

In fact, I suggest that you use the version of the tescase that I have
attached that does not run but counts the number of occurrences of 'new' in
the tree dump.

OK for master, certainly for 11-branch, when it is open again, and for
10-branch after a wait.

Are you reliant on others to commit and push your patches or have you done
the FSF paperwork?

Thanks

Paul




On Thu, 22 Apr 2021 at 21:50, José Rui Faustino de Sousa via Fortran <
fort...@gcc.gnu.org> wrote:

> Hi All!
>
> Proposed patch to:
>
> PR82376 - Duplicate function call using -fcheck=pointer
>
> Patch tested only on x86_64-pc-linux-gnu.
>
> Evaluate function result and then pass a pointer, instead of a reference
> to the function itself, thus avoiding multiple evaluations of the function.
>
> Thank you very much.
>
> Best regards,
> José Rui
>
> Fortran: Fix double function call with -fcheck=pointer [PR]
>
> gcc/fortran/ChangeLog:
>
> PR fortran/82376
> * trans-expr.c (gfc_conv_procedure_call): Evaluate function result
> and then pass a pointer.
>
> gcc/testsuite/ChangeLog:
>
> PR fortran/82376
> * gfortran.dg/PR82376.f90: New test.
>
>

-- 
"If you can't explain it simply, you don't understand it well enough" -
Albert Einstein
! { dg-do compile }
! { dg-options "-fdump-tree-original -fcheck=pointer" }
!
! Test the fix for PR82376. The pointer check was doubling up the call
! to new. The fix reduces the count of 'new' from 5 to 4.
!
! Contributed by José Rui Faustino de Sousa  
!
program main_p

  integer, parameter :: n = 10

  type :: foo_t
integer, pointer :: v =>null()
  end type foo_t

  integer, save :: pcnt = 0

  type(foo_t) :: int
  integer :: i

  do i = 1, n
call init(int, i)
if(.not.associated(int%v)) stop 1
if(int%v/=i) stop 2
if(pcnt/=i) stop 3
  end do

contains

  function new(data) result(this)
integer, target, intent(in) :: data

integer, pointer :: this

nullify(this)
this => data
pcnt = pcnt + 1
return
  end function new

  subroutine init(this, data)
type(foo_t), intent(out) :: this
integer, intent(in)  :: data

call set(this, new(data))
return
  end subroutine init

  subroutine set(this, that)
type(foo_t), intent(inout) :: this
integer, target, intent(in):: that

this%v => that
return
  end subroutine set

end program main_p
! { dg-final { scan-tree-dump-times "new" 4 "original" } }

[Patch, fortran] PR fortran/82376 - Duplicate function call using -fcheck=pointer

2021-04-22 Thread José Rui Faustino de Sousa via Gcc-patches

Hi All!

Proposed patch to:

PR82376 - Duplicate function call using -fcheck=pointer

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

Evaluate function result and then pass a pointer, instead of a reference 
to the function itself, thus avoiding multiple evaluations of the function.


Thank you very much.

Best regards,
José Rui

Fortran: Fix double function call with -fcheck=pointer [PR]

gcc/fortran/ChangeLog:

PR fortran/82376
* trans-expr.c (gfc_conv_procedure_call): Evaluate function result
and then pass a pointer.

gcc/testsuite/ChangeLog:

PR fortran/82376
* gfortran.dg/PR82376.f90: New test.

diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 213f32b0a67..b83b021755d 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -6014,11 +6014,8 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
 			|| (!e->value.function.esym
 && e->symtree->n.sym->attr.pointer))
 			&& fsym && fsym->attr.target)
-		{
-		  gfc_conv_expr (, e);
-		  parmse.expr = gfc_build_addr_expr (NULL_TREE, parmse.expr);
-		}
-
+		/* Make sure the function only gets called once.  */
+		gfc_conv_expr_reference (, e, false);
 	  else if (e->expr_type == EXPR_FUNCTION
 		   && e->symtree->n.sym->result
 		   && e->symtree->n.sym->result != e->symtree->n.sym
diff --git a/gcc/testsuite/gfortran.dg/PR82376.f90 b/gcc/testsuite/gfortran.dg/PR82376.f90
new file mode 100644
index 000..cea1c2ae211
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/PR82376.f90
@@ -0,0 +1,55 @@
+! { dg-do run }
+!
+! Test the fix for PR82376
+!
+
+program main_p
+
+  integer, parameter :: n = 10
+
+  type :: foo_t
+integer, pointer :: v =>null()
+  end type foo_t
+
+  integer, save :: pcnt = 0
+  
+  type(foo_t) :: int
+  integer :: i
+
+  do i = 1, n
+call init(int, i)
+if(.not.associated(int%v)) stop 1
+if(int%v/=i) stop 2
+if(pcnt/=i) stop 3
+  end do
+
+contains
+
+  function new(data) result(this)
+integer, target, intent(in) :: data
+
+integer, pointer :: this
+
+nullify(this)
+this => data
+pcnt = pcnt + 1
+return
+  end function new
+
+  subroutine init(this, data)
+type(foo_t), intent(out) :: this
+integer, intent(in)  :: data
+
+call set(this, new(data))
+return
+  end subroutine init
+
+  subroutine set(this, that)
+type(foo_t), intent(inout) :: this
+integer, target, intent(in):: that
+
+this%v => that
+return
+  end subroutine set
+  
+end program main_p