diff mbox series

[Fortran] PR92284 – gfc_desc_to_cfi_desc fixes

Message ID fb89740d-7919-d33f-5f6e-18eb64b68f41@codesourcery.com
State New
Headers show
Series [Fortran] PR92284 – gfc_desc_to_cfi_desc fixes | expand

Commit Message

Tobias Burnus Oct. 30, 2019, 11:29 p.m. UTC
Playing with the PR92284 test case revealed two issues related to 
gfc_desc_to_cfi_desc:

* Access of uninitialized memory – copying the array bounds (in 
libgfortran) does not make sense for unallocted allocatables and 
nullified pointers. Hence, check for "<descr>.data == NULL".

* There is a memory leak. I misunderstood the dump when fixing PR91863 
(rev.277502).
https://gcc.gnu.org/ml/gcc-patches/2019-10/msg01651.html

Regarding the latter: If one passed gfc_desc_to_cfi_desc a pointer var, 
pointing to NULL, as CFI (Bind(C) array descriptor) argument, 
libgfortran allocates the memory for the descriptor – which at some 
point has to be freed.

Contrary to the original version, one can free that memory 
unconditionally. (Not only because "free" handles NULL pointers but – 
unless "malloc" failed – we know that ptr has been malloced.) I also 
tried to make the comments a bit clearer.

Build and regtested.
OK for trunk and GCC 9 (the latter is also affected)?

Tobias

PR: Related pending patch: 
https://gcc.gnu.org/ml/gcc-patches/2019-10/msg02148.html
Also missing: At the end of a bind(C) procedure written in Fortran, 
allocatable/pointers array arguments need get updated: the "data" and 
the bounds part of the array descriptor might have changed while running 
the procedure body. Cf. this PR and PR 92189

Comments

Paul Richard Thomas Oct. 31, 2019, 9:46 a.m. UTC | #1
Hi Tobias,

OK for trunk and for 9-branch. As with the patch for PR92277, you will
have to get release manager approval for 9.2.

Thanks for working on this.

Cheers

Paul

On Wed, 30 Oct 2019 at 23:29, Tobias Burnus <tobias@codesourcery.com> wrote:
>
> Playing with the PR92284 test case revealed two issues related to
> gfc_desc_to_cfi_desc:
>
> * Access of uninitialized memory – copying the array bounds (in
> libgfortran) does not make sense for unallocted allocatables and
> nullified pointers. Hence, check for "<descr>.data == NULL".
>
> * There is a memory leak. I misunderstood the dump when fixing PR91863
> (rev.277502).
> https://gcc.gnu.org/ml/gcc-patches/2019-10/msg01651.html
>
> Regarding the latter: If one passed gfc_desc_to_cfi_desc a pointer var,
> pointing to NULL, as CFI (Bind(C) array descriptor) argument,
> libgfortran allocates the memory for the descriptor – which at some
> point has to be freed.
>
> Contrary to the original version, one can free that memory
> unconditionally. (Not only because "free" handles NULL pointers but –
> unless "malloc" failed – we know that ptr has been malloced.) I also
> tried to make the comments a bit clearer.
>
> Build and regtested.
> OK for trunk and GCC 9 (the latter is also affected)?
>
> Tobias
>
> PR: Related pending patch:
> https://gcc.gnu.org/ml/gcc-patches/2019-10/msg02148.html
> Also missing: At the end of a bind(C) procedure written in Fortran,
> allocatable/pointers array arguments need get updated: the "data" and
> the bounds part of the array descriptor might have changed while running
> the procedure body. Cf. this PR and PR 92189
>
Jakub Jelinek Oct. 31, 2019, 4:41 p.m. UTC | #2
On Thu, Oct 31, 2019 at 12:29:05AM +0100, Tobias Burnus wrote:
>  	gcc/testsuite/
> 	PR fortran/92284.

Note, no . at the end

> 	* gfortran.dg/bind-c-intent-out.f90: Update expected dump;
> 	extend comment.
> 	* gfortran.dg/bind_c_array_params_3.f90: New.
> 	* gfortran.dg/bind_c_array_params_3_aux.c: New.

This test breaks for me on Fedora, as ISO_Fortran_binding.h header isn't
found.  All other gfortran.dg tests that use this header include it with
full relative path, so I've committed this as obvious to trunk
after retesting it fixes the issue:

2019-10-31  Jakub Jelinek  <jakub@redhat.com>

	PR fortran/92284
	* gfortran.dg/bind_c_array_params_3_aux.c: Include
	../../../libgfortran/ISO_Fortran_binding.h rather than
	ISO_Fortran_binding.h.

--- gcc/testsuite/gfortran.dg/bind_c_array_params_3_aux.c.jj	2019-10-31 13:35:20.572889538 +0100
+++ gcc/testsuite/gfortran.dg/bind_c_array_params_3_aux.c	2019-10-31 17:30:23.192165458 +0100
@@ -5,7 +5,7 @@
 #include <errno.h>
 #include <stdio.h>
 
-#include "ISO_Fortran_binding.h"
+#include "../../../libgfortran/ISO_Fortran_binding.h"
 
 void arr_set_c(CFI_cdesc_t*);
 
@@ -24,4 +24,3 @@ void arr_set_c(CFI_cdesc_t *arr){
   for(i=0; i<ub[0]-lb[0]+1; i++) auxp[i]=i;
   return;
 }
-

	Jakub
Tobias Burnus Nov. 4, 2019, 2:24 p.m. UTC | #3
I have now committed the patch to the GCC 9 branch – and added the test 
case for PR92277 (the ICE was a GCC 10 regression, only). – Rev. 277781.

Thanks for the review.

Tobias

PS: The release-manage item came up because the GCC home page linked to 
the wrong GCC 9 status report (pre-9.2 release instead of post-9.2 
release; both: August 2019). [Now fixed.]

On 10/31/19 10:46 AM, Paul Richard Thomas wrote:
> Hi Tobias,
>
> OK for trunk and for 9-branch. As with the patch for PR92277, you will
> have to get release manager approval for 9.2.
>
> Thanks for working on this.
>
> Cheers
>
> Paul
>
> On Wed, 30 Oct 2019 at 23:29, Tobias Burnus <tobias@codesourcery.com> wrote:
>> Playing with the PR92284 test case revealed two issues related to
>> gfc_desc_to_cfi_desc:
>>
>> * Access of uninitialized memory – copying the array bounds (in
>> libgfortran) does not make sense for unallocted allocatables and
>> nullified pointers. Hence, check for "<descr>.data == NULL".
>>
>> * There is a memory leak. I misunderstood the dump when fixing PR91863
>> (rev.277502).
>> https://gcc.gnu.org/ml/gcc-patches/2019-10/msg01651.html
>>
>> Regarding the latter: If one passed gfc_desc_to_cfi_desc a pointer var,
>> pointing to NULL, as CFI (Bind(C) array descriptor) argument,
>> libgfortran allocates the memory for the descriptor – which at some
>> point has to be freed.
>>
>> Contrary to the original version, one can free that memory
>> unconditionally. (Not only because "free" handles NULL pointers but –
>> unless "malloc" failed – we know that ptr has been malloced.) I also
>> tried to make the comments a bit clearer.
>>
>> Build and regtested.
>> OK for trunk and GCC 9 (the latter is also affected)?
>>
>> Tobias
>>
>> PR: Related pending patch:
>> https://gcc.gnu.org/ml/gcc-patches/2019-10/msg02148.html
>> Also missing: At the end of a bind(C) procedure written in Fortran,
>> allocatable/pointers array arguments need get updated: the "data" and
>> the bounds part of the array descriptor might have changed while running
>> the procedure body. Cf. this PR and PR 92189
>>
>
diff mbox series

Patch

	gcc/fortran/
	PR fortran/92284.
	* trans-expr.c (gfc_conv_gfc_desc_to_cfi_desc): Free CFI descriptor
	at the end; partial revised revert of Rev. 277502.

 	libgfortran/
	PR fortran/92284.
	* runtime/ISO_Fortran_binding.c (gfc_desc_to_cfi_desc):

 	gcc/testsuite/
	PR fortran/92284.
	* gfortran.dg/bind-c-intent-out.f90: Update expected dump;
	extend comment.
	* gfortran.dg/bind_c_array_params_3.f90: New.
	* gfortran.dg/bind_c_array_params_3_aux.c: New.

diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 7eba1bbd082..f800faaa4e5 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -5303,13 +5303,13 @@  gfc_conv_gfc_desc_to_cfi_desc (gfc_se *parmse, gfc_expr *e, gfc_symbol *fsym)
   /* Now pass the gfc_descriptor by reference.  */
   parmse->expr = gfc_build_addr_expr (NULL_TREE, parmse->expr);
 
-  /* Variables to point to the gfc and CFI descriptors.  */
+  /* Variables to point to the gfc and CFI descriptors; cfi = NULL implies
+     that the CFI descriptor is allocated by the gfor_fndecl_gfc_to_cfi call.  */
   gfc_desc_ptr = parmse->expr;
   cfi_desc_ptr = gfc_create_var (pvoid_type_node, "cfi");
-  gfc_add_modify (&parmse->pre, cfi_desc_ptr,
-		  build_int_cst (pvoid_type_node, 0));
+  gfc_add_modify (&parmse->pre, cfi_desc_ptr, null_pointer_node);
 
-  /* Allocate the CFI descriptor and fill the fields.  */
+  /* Allocate the CFI descriptor itself and fill the fields.  */
   tmp = gfc_build_addr_expr (NULL_TREE, cfi_desc_ptr);
   tmp = build_call_expr_loc (input_location,
 			     gfor_fndecl_gfc_to_cfi, 2, tmp, gfc_desc_ptr);
@@ -5324,6 +5324,10 @@  gfc_conv_gfc_desc_to_cfi_desc (gfc_se *parmse, gfc_expr *e, gfc_symbol *fsym)
   /* The CFI descriptor is passed to the bind_C procedure.  */
   parmse->expr = cfi_desc_ptr;
 
+  /* Free the CFI descriptor.  */
+  tmp = gfc_call_free (cfi_desc_ptr);
+  gfc_prepend_expr_to_block (&parmse->post, tmp);
+
   /* Transfer values back to gfc descriptor.  */
   tmp = gfc_build_addr_expr (NULL_TREE, parmse->expr);
   tmp = build_call_expr_loc (input_location,
diff --git a/gcc/testsuite/gfortran.dg/bind-c-intent-out.f90 b/gcc/testsuite/gfortran.dg/bind-c-intent-out.f90
index 493e546d45d..39822c0753a 100644
--- a/gcc/testsuite/gfortran.dg/bind-c-intent-out.f90
+++ b/gcc/testsuite/gfortran.dg/bind-c-intent-out.f90
@@ -35,7 +35,8 @@  end program p
 ! the intent(out) implies freeing in the callee (!), hence the "free"
 ! It is the only 'free' as 'a' is part of the main program and, hence, implicitly has the SAVE attribute.
 ! The  'cfi = 0' appears before the call due to the deallocate and when preparing the C descriptor
+! As cfi (i.e. the descriptor itself) is allocated in libgomp, it has to be freed after the call.
 
-! { dg-final { scan-tree-dump-times "__builtin_free" 1 "original" } }
-! { dg-final { scan-tree-dump-times "__builtin_free \\(cfi\\.\[0-9\]+\\);" 1 "original" } }
+! { dg-final { scan-tree-dump-times "__builtin_free" 2 "original" } }
+! { dg-final { scan-tree-dump-times "__builtin_free \\(cfi\\.\[0-9\]+\\);" 2 "original" } }
 ! { dg-final { scan-tree-dump-times "cfi\\.\[0-9\]+ = 0B;" 2 "original" } }
diff --git a/gcc/testsuite/gfortran.dg/bind_c_array_params_3.f90 b/gcc/testsuite/gfortran.dg/bind_c_array_params_3.f90
new file mode 100644
index 00000000000..d5bad7d03f2
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bind_c_array_params_3.f90
@@ -0,0 +1,39 @@ 
+! { dg-do run }
+! { dg-additional-sources bind_c_array_params_3_aux.c }
+!
+! PR fortran/92284
+!
+! Contributed by José Rui Faustino de Sousa
+!
+program arr_p
+  use, intrinsic :: iso_c_binding, only: c_int
+  implicit none (type, external)
+
+  integer(kind=c_int), pointer :: arr(:)
+  integer :: i
+
+  nullify(arr)
+  call arr_set(arr)
+
+  if (.not.associated(arr)) stop 1
+  if (lbound(arr,dim=1) /= 1) stop 2
+  if (ubound(arr,dim=1) /= 9) stop 3
+  if (any (arr /= [(i, i=0,8)])) stop 4
+  deallocate(arr)
+
+contains
+
+  subroutine arr_set(this) !bind(c)
+    integer(kind=c_int), pointer, intent(out) :: this(:)
+
+    interface
+      subroutine arr_set_c(this) bind(c)
+        use, intrinsic :: iso_c_binding, only: c_int
+        implicit none
+        integer(kind=c_int), pointer, intent(out) :: this(:)
+      end subroutine arr_set_c
+    end interface
+
+    call arr_set_c(this)
+  end subroutine arr_set
+end program arr_p
diff --git a/gcc/testsuite/gfortran.dg/bind_c_array_params_3_aux.c b/gcc/testsuite/gfortran.dg/bind_c_array_params_3_aux.c
new file mode 100644
index 00000000000..6e13aa3b2ef
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bind_c_array_params_3_aux.c
@@ -0,0 +1,27 @@ 
+/* Used by bind_c_array_params_3.f90.  */
+/* PR fortran/92284.  */
+
+#include <assert.h>
+#include <errno.h>
+#include <stdio.h>
+
+#include "ISO_Fortran_binding.h"
+
+void arr_set_c(CFI_cdesc_t*);
+
+void arr_set_c(CFI_cdesc_t *arr){
+  int i, stat, *auxp = NULL;
+  CFI_index_t   lb[] = {1};
+  CFI_index_t   ub[] = {9};
+  
+  assert(arr);
+  assert(arr->rank==1);
+  assert(!arr->base_addr);
+  stat = CFI_allocate(arr, lb, ub, sizeof(int));
+  assert(stat==CFI_SUCCESS);
+  auxp = (int*)arr->base_addr;
+  assert(auxp);
+  for(i=0; i<ub[0]-lb[0]+1; i++) auxp[i]=i;
+  return;
+}
+
diff --git a/libgfortran/runtime/ISO_Fortran_binding.c b/libgfortran/runtime/ISO_Fortran_binding.c
index 695ef57ac32..c71d8e89453 100644
--- a/libgfortran/runtime/ISO_Fortran_binding.c
+++ b/libgfortran/runtime/ISO_Fortran_binding.c
@@ -119,24 +119,25 @@  gfc_desc_to_cfi_desc (CFI_cdesc_t **d_ptr, const gfc_array_void *s)
     d->type = (CFI_type_t)(d->type
 		+ ((CFI_type_t)d->elem_len << CFI_type_kind_shift));
 
-  /* Full pointer or allocatable arrays retain their lower_bounds.  */
-  for (n = 0; n < GFC_DESCRIPTOR_RANK (s); n++)
-    {
-      if (d->attribute != CFI_attribute_other)
-	d->dim[n].lower_bound = (CFI_index_t)GFC_DESCRIPTOR_LBOUND(s, n);
-      else
-	d->dim[n].lower_bound = 0;
-
-      /* Assumed size arrays have gfc ubound == 0 and CFI extent = -1.  */
-      if ((n == GFC_DESCRIPTOR_RANK (s) - 1)
-	  && GFC_DESCRIPTOR_LBOUND(s, n) == 1
-	  && GFC_DESCRIPTOR_UBOUND(s, n) == 0)
-	d->dim[n].extent = -1;
-      else
-	d->dim[n].extent = (CFI_index_t)GFC_DESCRIPTOR_UBOUND(s, n)
-			    - (CFI_index_t)GFC_DESCRIPTOR_LBOUND(s, n) + 1;
-      d->dim[n].sm = (CFI_index_t)(GFC_DESCRIPTOR_STRIDE(s, n) * s->span);
-    }
+  if (d->base_addr)
+    /* Full pointer or allocatable arrays retain their lower_bounds.  */
+    for (n = 0; n < GFC_DESCRIPTOR_RANK (s); n++)
+      {
+	if (d->attribute != CFI_attribute_other)
+	  d->dim[n].lower_bound = (CFI_index_t)GFC_DESCRIPTOR_LBOUND(s, n);
+	else
+	  d->dim[n].lower_bound = 0;
+
+	/* Assumed size arrays have gfc ubound == 0 and CFI extent = -1.  */
+	if (n == GFC_DESCRIPTOR_RANK (s) - 1
+	    && GFC_DESCRIPTOR_LBOUND(s, n) == 1
+	    && GFC_DESCRIPTOR_UBOUND(s, n) == 0)
+	  d->dim[n].extent = -1;
+	else
+	  d->dim[n].extent = (CFI_index_t)GFC_DESCRIPTOR_UBOUND(s, n)
+			     - (CFI_index_t)GFC_DESCRIPTOR_LBOUND(s, n) + 1;
+	d->dim[n].sm = (CFI_index_t)(GFC_DESCRIPTOR_STRIDE(s, n) * s->span);
+      }
 
   if (*d_ptr == NULL)
     *d_ptr = d;