Bug 64209 - [OOP] runtime segfault with CLASS(*), INTENT(OUT) dummy argument
Summary: [OOP] runtime segfault with CLASS(*), INTENT(OUT) dummy argument
Status: RESOLVED FIXED
Alias: None
Product: gcc
Classification: Unclassified
Component: fortran (show other bugs)
Version: 5.0
: P3 normal
Target Milestone: 5.0
Assignee: janus
URL:
Keywords: wrong-code
Depends on:
Blocks:
 
Reported: 2014-12-06 16:00 UTC by Miha Polajnar
Modified: 2016-11-16 17:27 UTC (History)
1 user (show)

See Also:
Host:
Target:
Build:
Known to work:
Known to fail:
Last reconfirmed: 2014-12-09 00:00:00


Attachments
Source code describing the bug (460 bytes, text/x-fortran)
2014-12-06 16:00 UTC, Miha Polajnar
Details

Note You need to log in before you can comment on or make changes to this bug.
Description Miha Polajnar 2014-12-06 16:00:42 UTC
Created attachment 34209 [details]
Source code describing the bug

The attached source code produces segmentation fault :

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7FA69CC6F4D0
#1  0x7FA69CC6E6B0
#2  0x7FA69C17E54F
#3  0x4011FC in __copy_INTEGER_4_.3528 at gfort_bug.f90:?
#4  0x4010B0 in __m_MOD_copy
#5  0x401411 in MAIN__ at gfort_bug.f90:?
Segmentation fault

with 

gcc version 5.0.0 20141202 (experimental) [trunk revision 218267] (SUSE Linux).

The code works fine with ifort.
Comment 1 Dominique d'Humieres 2014-12-09 19:26:56 UTC
Confirmed from 4.8.3 up to trunk (5.0).
Comment 2 janus 2014-12-18 19:20:00 UTC
I could boil it down to this much simpler case:

PROGRAM main
  IMPLICIT NONE
  INTEGER :: x, y
  x = 5
  CALL copy(x,y)
  PRINT *,y
contains
  SUBROUTINE copy(a,b)
    integer, INTENT(IN) :: a
    CLASS(*), INTENT(OUT) :: b
    SELECT TYPE(b); TYPE IS(integer)
      b = a
    END SELECT
  END SUBROUTINE
END

Segfaults with 4.8, 4.9 and trunk. Earlier versions don't support unlimited polymorphism.

Had a quick look over the dump, but could not directly see where things go wrong.
Comment 3 janus 2014-12-18 20:58:42 UTC
-fdump-tree-original shows the following dump of the copy function (with gfortran 4.8):


copy (integer(kind=4) & restrict a, struct __class__STAR & restrict b)
{
  {
    integer(kind=4) * __tmp_INTEGER_4;

    (void) __builtin_memcpy (b->_data, (void *) b->_vptr->_def_init, (unsigned long) b->_vptr->_size);
    switch (b->_vptr->_hash)
      {
        case 177599:;
        __tmp_INTEGER_4 = (integer(kind=4) *) b->_data;
        *__tmp_INTEGER_4 = *a;
        L.5:;
        goto L.3;
      }
    L.3:;
    L.2:;
    L.1:;
  }
}


With 4.9 and trunk additional code is initialized for calling a finalizer, but since the failure occurs already with 4.8, the problem must be in here already.

Now, the error goes away if one removes the INTENT(OUT). The only thing that changes in the dump is that the __builtin_memcpy call is removed, which means that this line must be the cuplrit.

After staring at it for a while, I concluded that the call to __builtin_memcpy itself looks fine. The problem is that the _def_init component is NULL in the case at hand (which can be seen the full dump, not shown here).

So I guess all were missing is a line like

if (b->_vptr->_def_init != NULL)

before the __builtin_memcpy.
Comment 4 janus 2014-12-18 22:07:11 UTC
The following patch is sufficient to make the reduced test case in comment 2 work:


Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(Revision 218874)
+++ gcc/fortran/trans-expr.c	(Arbeitskopie)
@@ -980,6 +980,9 @@ gfc_trans_class_init_assign (gfc_code *code)
       src.expr = gfc_build_addr_expr (NULL_TREE, src.expr);
 
       tmp = gfc_build_memcpy_call (dst.expr, src.expr, memsz.expr);
+
+      tmp = build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp),
+			src.expr, tmp, build_empty_stmt (input_location));
     }
 
   if (code->expr1->symtree->n.sym->attr.optional


However, the original test case in comment 0 still segfaults, so there seems to be yet another problem.
Comment 5 janus 2014-12-18 22:53:51 UTC
(In reply to janus from comment #4)
> The following patch is sufficient to make the reduced test case in comment 2
> work:

... but unfortunately it caused a number of testsuite regressions. The following variant is clean:


Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(Revision 218874)
+++ gcc/fortran/trans-expr.c	(Arbeitskopie)
@@ -943,7 +943,7 @@ tree
 gfc_trans_class_init_assign (gfc_code *code)
 {
   stmtblock_t block;
-  tree tmp;
+  tree tmp, cond;
   gfc_se dst,src,memsz;
   gfc_expr *lhs, *rhs, *sz;
 
@@ -980,6 +980,12 @@ gfc_trans_class_init_assign (gfc_code *code)
       src.expr = gfc_build_addr_expr (NULL_TREE, src.expr);
 
       tmp = gfc_build_memcpy_call (dst.expr, src.expr, memsz.expr);
+
+      cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node,
+			      src.expr, fold_convert (TREE_TYPE (src.expr),
+						      null_pointer_node));
+      tmp = build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp), cond, tmp,
+			build_empty_stmt (input_location));
     }
 
   if (code->expr1->symtree->n.sym->attr.optional


Still, it does not cure the segfault in comment 0.
Comment 6 janus 2014-12-18 23:24:41 UTC
Here is a reduced test case for the remaining segfault:

PROGRAM main
  IMPLICIT NONE
  INTEGER :: copy_x(3)
  CALL copy(1,copy_x)
  PRINT *, copy_x
CONTAINS
  SUBROUTINE copy(x,a)
    integer, INTENT(IN) :: x
    CLASS(*), INTENT(OUT) :: a(:)
      SELECT TYPE(a); TYPE IS(integer)
	a(:) = x
      END SELECT
  END SUBROUTINE
END PROGRAM


It's a very similar scheme as in comment #2, only this time we have an array-valued CLASS(*), INTENT(OUT) argument.


I think the problem is with _def_init being NULL again. For the array case here the dump shown a line like:

    a->_vptr->_copy (a->_vptr->_def_init, &a->_data);

Again we need a conditional check for _def_init being non-NULL.
Comment 7 janus 2014-12-19 19:29:28 UTC
Author: janus
Date: Fri Dec 19 19:28:57 2014
New Revision: 218968

URL: https://gcc.gnu.org/viewcvs?rev=218968&root=gcc&view=rev
Log:
2014-12-19  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/64209
	* trans-expr.c (gfc_trans_class_array_init_assign): Check if _def_init
	component is non-NULL.
	(gfc_trans_class_init_assign): Ditto.

2014-12-19  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/64209
	* gfortran.dg/unlimited_polymorphic_19.f90: New.

Added:
    trunk/gcc/testsuite/gfortran.dg/unlimited_polymorphic_19.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog
Comment 8 janus 2014-12-19 19:32:34 UTC
Fixed on trunk with r218968. Closing.

Thanks for the report!