https://gcc.gnu.org/bugzilla/show_bug.cgi?id=87284

            Bug ID: 87284
           Summary: [7/8/9 Regression] Allocation of class arrays with
                    mold results in "conditional jump or move depends on
                    uninitialised value"
           Product: gcc
           Version: 8.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: pault at gcc dot gnu.org
          Reporter: pault at gcc dot gnu.org
  Target Milestone: ---

Reported by Andrew Baldwin on clf:

      MODULE INTS_TYPE_MODULE
        TYPE, ABSTRACT :: BASE_TYPE
        END TYPE BASE_TYPE

        TYPE, EXTENDS (BASE_TYPE) :: INTS_TYPE
          INTEGER, ALLOCATABLE :: INTS(:)
        END TYPE INTS_TYPE
      CONTAINS
        SUBROUTINE MOLD_ALLOCATE (IT_OBJS, MOLD_OBJ)
          CLASS (BASE_TYPE), ALLOCATABLE, INTENT (OUT) :: IT_OBJS(:)
          CLASS (BASE_TYPE), INTENT (IN) :: MOLD_OBJ

          ALLOCATE (IT_OBJS(2), mold = MOLD_OBJ)

          RETURN
        END SUBROUTINE MOLD_ALLOCATE
      END MODULE INTS_TYPE_MODULE

      PROGRAM MFE
        USE INTS_TYPE_MODULE
        IMPLICIT NONE

        CLASS (BASE_TYPE), ALLOCATABLE :: IT_OBJS(:)
        INTEGER :: I
        TYPE (INTS_TYPE) :: MOLD_OBJ

        ALLOCATE (INTS_TYPE :: IT_OBJS(2))

        SELECT TYPE (IT_OBJS)
        TYPE IS (INTS_TYPE)
          ALLOCATE (IT_OBJS(1)%INTS(10))

          ALLOCATE (IT_OBJS(2)%INTS(10))
        END SELECT


        DEALLOCATE (IT_OBJS)

        CALL MOLD_ALLOCATE (IT_OBJS, MOLD_OBJ)

        IF (ALLOCATED(IT_OBJS)) THEN
          IF (SIZE(IT_OBJS) .GE. 2) THEN
            SELECT TYPE (IT_OBJS)
            TYPE IS (INTS_TYPE)
              ALLOCATE (IT_OBJS(1)%INTS(10))

              ALLOCATE (IT_OBJS(2)%INTS(10))
            END SELECT
          END IF
        END IF
      END PROGRAM MFE

It produces the following code for the initialization after the allocation in
'mold_allocate':

    {
      struct base_type[0:] * restrict D.3905;
      integer(kind=8) D.3906;
      integer(kind=8) D.3907;
      integer(kind=8) D.3908;
      struct base_type * D.3909;

      D.3905 = (struct base_type[0:] * restrict) it_objs->_data.data;
      D.3906 = it_objs->_data.offset;
      D.3907 = it_objs->_data.dim[0].lbound;
      D.3908 = it_objs->_data.dim[0].ubound;

/* This is OK - init expr for the dynamic type.  */

      D.3909 = it_objs->_vptr->_def_init;
      {
        integer(kind=8) S.7;

        S.7 = D.3907;
        while (1)
          {
            if (S.7 > D.3908) goto L.11;

/* Copied to elements of the base type!!!!  */

            it_objs->_vptr->_copy (D.3909, &(*D.3905)[S.7 + D.3906]);
            S.7 = S.7 + 1;
          }
        L.11:;
      }
    }

A trivial fix regtests OK:
Index: gcc/fortran/trans-expr.c
===================================================================
*** gcc/fortran/trans-expr.c    (revision 264209)
--- gcc/fortran/trans-expr.c    (working copy)
*************** gfc_trans_class_init_assign (gfc_code *c
*** 1505,1511 ****
    gfc_start_block (&block);

    lhs = gfc_copy_expr (code->expr1);
-   gfc_add_data_component (lhs);

    rhs = gfc_copy_expr (code->expr1);
    gfc_add_vptr_component (rhs);
--- 1505,1510 ----
*************** gfc_trans_class_init_assign (gfc_code *c
*** 1528,1533 ****
--- 1527,1533 ----
      }
    else
      {
+       gfc_add_data_component (lhs);
        sz = gfc_copy_expr (code->expr1);
        gfc_add_vptr_component (sz);
        gfc_add_size_component (sz);

It will be committed as 'obvious' when I have a moment.

Paul

Reply via email to