]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
re PR fortran/84546 (Bad sourced allocation of CLASS(*) with source with CLASS(*...
authorPaul Thomas <pault@gcc.gnu.org>
Wed, 16 May 2018 09:35:19 +0000 (09:35 +0000)
committerPaul Thomas <pault@gcc.gnu.org>
Wed, 16 May 2018 09:35:19 +0000 (09:35 +0000)
2018-05-16  Paul Thomas  <pault@gcc.gnu.org>

PR fortran/84546
Backport from trunk
* trans-array.c (structure_alloc_comps): Make sure that the
vptr is copied and that the unlimited polymorphic _len is used
to compute the size to be allocated.
(build_array_ref): Set the 'unlimited' argument false in the
call to gfc_get_class_array_ref.
* trans-expr.c (gfc_get_class_array_ref): If unlimited, use the
unlimited polymorphic _len for the offset to the element.
(gfc_copy_class_to_class): Set the new 'unlimited' argument.
* trans.h : Add the boolean 'unlimited' to the prototype.

2018-05-16  Paul Thomas  <pault@gcc.gnu.org>

PR fortran/84546
Backport from trunk
* gfortran.dg/unlimited_polymorphic_29.f90 : New test.

From-SVN: r260281

gcc/fortran/ChangeLog
gcc/fortran/trans-array.c
gcc/fortran/trans-expr.c
gcc/fortran/trans.h
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/unlimited_polymorphic_29.f90 [new file with mode: 0644]

index ebb21479d07433acb675d6f8f0455234f28c3537..a8cac67fe0bb5d52eab990f568962bf02e68c6c4 100644 (file)
@@ -1,9 +1,23 @@
+2018-05-16  Paul Thomas  <pault@gcc.gnu.org>
+
+       PR fortran/84546
+       Backport from trunk
+       * trans-array.c (structure_alloc_comps): Make sure that the
+       vptr is copied and that the unlimited polymorphic _len is used
+       to compute the size to be allocated.
+       (build_array_ref): Set the 'unlimited' argument false in the
+       call to gfc_get_class_array_ref.
+       * trans-expr.c (gfc_get_class_array_ref): If unlimited, use the
+       unlimited polymorphic _len for the offset to the element.
+       (gfc_copy_class_to_class): Set the new 'unlimited' argument.
+       * trans.h : Add the boolean 'unlimited' to the prototype.
+
 2018-05-12  Steven G. Kargl  <kargl@gcc.gnu.org>
 
        PR fortran/85542
        Backport from trunk
        * expr.c (check_inquiry): Avoid NULL pointer dereference.
+
 2018-05-12  Paul Thomas  <pault@gcc.gnu.org>
 
        PR fortran/68846
index c44656bb9ae8cc8c22d8f7c59e869a870829488b..9a3290edc3be3dfb921cfdbb7f0e081def47bdef 100644 (file)
@@ -3338,7 +3338,10 @@ build_array_ref (tree desc, tree offset, tree decl, tree vptr)
     {
       type = gfc_get_element_type (type);
       tmp = TREE_OPERAND (cdecl, 0);
-      tmp = gfc_get_class_array_ref (offset, tmp, NULL_TREE);
+      /* Note that the fourth argument in this call has been set false.
+        should any character dynamic types come this way, the 'len'
+        field of the unlimited object will not be used.  */
+      tmp = gfc_get_class_array_ref (offset, tmp, NULL_TREE, false);
       tmp = fold_convert (build_pointer_type (type), tmp);
       tmp = build_fold_indirect_ref_loc (input_location, tmp);
       return tmp;
@@ -8650,6 +8653,31 @@ structure_alloc_comps (gfc_symbol * der_type, tree decl,
 
              gfc_init_block (&tmpblock);
 
+             gfc_add_modify (&tmpblock, gfc_class_vptr_get (dcmp),
+                             gfc_class_vptr_get (comp));
+
+             /* Copy the unlimited '_len' field. If it is greater than zero
+                (ie. a character(_len)), multiply it by size and use this
+                for the malloc call.  */
+             if (UNLIMITED_POLY (c))
+               {
+                 tree ctmp;
+                 gfc_add_modify (&tmpblock, gfc_class_len_get (dcmp),
+                                 gfc_class_len_get (comp));
+
+                 size = gfc_evaluate_now (size, &tmpblock);
+                 tmp = gfc_class_len_get (comp);
+                 ctmp = fold_build2_loc (input_location, MULT_EXPR,
+                                         size_type_node, size,
+                                         fold_convert (size_type_node, tmp));
+                 tmp = fold_build2_loc (input_location, GT_EXPR,
+                                        logical_type_node, tmp,
+                                        build_zero_cst (TREE_TYPE (tmp)));
+                 size = fold_build3_loc (input_location, COND_EXPR,
+                                         size_type_node, tmp, ctmp, size);
+                 size = gfc_evaluate_now (size, &tmpblock);
+               }
+
              /* Coarray component have to have the same allocation status and
                 shape/type-parameter/effective-type on the LHS and RHS of an
                 intrinsic assignment. Hence, we did not deallocated them - and
index 49486c5328aaa19af80b683895e3b024adcfbac5..e1205e36b97c9d4bfb4ec11f856d65e33f62a6b8 100644 (file)
@@ -1156,15 +1156,32 @@ gfc_conv_class_to_class (gfc_se *parmse, gfc_expr *e, gfc_typespec class_ts,
    of the referenced element.  */
 
 tree
-gfc_get_class_array_ref (tree index, tree class_decl, tree data_comp)
+gfc_get_class_array_ref (tree index, tree class_decl, tree data_comp,
+                        bool unlimited)
 {
-  tree data = data_comp != NULL_TREE ? data_comp :
-                                      gfc_class_data_get (class_decl);
-  tree size = gfc_class_vtab_size_get (class_decl);
-  tree offset = fold_build2_loc (input_location, MULT_EXPR,
-                                gfc_array_index_type,
-                                index, size);
-  tree ptr;
+  tree data, size, tmp, ctmp, offset, ptr;
+
+  data = data_comp != NULL_TREE ? data_comp :
+                                 gfc_class_data_get (class_decl);
+  size = gfc_class_vtab_size_get (class_decl);
+
+  if (unlimited)
+    {
+      tmp = fold_convert (gfc_array_index_type,
+                         gfc_class_len_get (class_decl));
+      ctmp = fold_build2_loc (input_location, MULT_EXPR,
+                             gfc_array_index_type, size, tmp);
+      tmp = fold_build2_loc (input_location, GT_EXPR,
+                            logical_type_node, tmp,
+                            build_zero_cst (TREE_TYPE (tmp)));
+      size = fold_build3_loc (input_location, COND_EXPR,
+                             gfc_array_index_type, tmp, ctmp, size);
+    }
+
+  offset = fold_build2_loc (input_location, MULT_EXPR,
+                           gfc_array_index_type,
+                           index, size);
+
   data = gfc_conv_descriptor_data_get (data);
   ptr = fold_convert (pvoid_type_node, data);
   ptr = fold_build_pointer_plus_loc (input_location, ptr, offset);
@@ -1266,14 +1283,15 @@ gfc_copy_class_to_class (tree from, tree to, tree nelems, bool unlimited)
 
       if (is_from_desc)
        {
-         from_ref = gfc_get_class_array_ref (index, from, from_data);
+         from_ref = gfc_get_class_array_ref (index, from, from_data,
+                                             unlimited);
          vec_safe_push (args, from_ref);
        }
       else
         vec_safe_push (args, from_data);
 
       if (is_to_class)
-       to_ref = gfc_get_class_array_ref (index, to, to_data);
+       to_ref = gfc_get_class_array_ref (index, to, to_data, unlimited);
       else
        {
          tmp = gfc_conv_array_data (to);
index d02f3470eebc00e95e1e51e1094f43a2e9ad2e72..4fcc389a53b850d41bf6665cbb709c2bad91955b 100644 (file)
@@ -431,7 +431,7 @@ tree gfc_vptr_deallocate_get (tree);
 void gfc_reset_vptr (stmtblock_t *, gfc_expr *);
 void gfc_reset_len (stmtblock_t *, gfc_expr *);
 tree gfc_get_vptr_from_expr (tree);
-tree gfc_get_class_array_ref (tree, tree, tree);
+tree gfc_get_class_array_ref (tree, tree, tree, bool);
 tree gfc_copy_class_to_class (tree, tree, tree, bool);
 bool gfc_add_finalizer_call (stmtblock_t *, gfc_expr *);
 bool gfc_add_comp_finalizer_call (stmtblock_t *, tree, gfc_component *, bool);
index 7610ddb10d6c2dfa305b8f5f9f6cd2c3c3b4de8d..ae967c4c640e288f6aa30b4466bf0e6f38f23567 100644 (file)
@@ -1,3 +1,9 @@
+2018-05-16  Paul Thomas  <pault@gcc.gnu.org>
+
+       PR fortran/84546
+       Backport from trunk
+       * gfortran.dg/unlimited_polymorphic_29.f90 : New test.
+
 2018-05-12  Steven G. Kargl  <kargl@gcc.gnu.org>
 
        PR fortran/85542
diff --git a/gcc/testsuite/gfortran.dg/unlimited_polymorphic_29.f90 b/gcc/testsuite/gfortran.dg/unlimited_polymorphic_29.f90
new file mode 100644 (file)
index 0000000..d4ad39c
--- /dev/null
@@ -0,0 +1,84 @@
+! { dg-do run }
+!
+! Test the fix for PR84546 in which the failing cases would
+! have x%vec = ['foo','b   '].
+!
+! Contributed by Neil Carlson  <neil.n.carlson@gmail.com>
+!
+module any_vector_type
+
+  type :: any_vector
+    class(*), allocatable :: vec(:)
+  end type
+
+  interface any_vector
+    procedure any_vector1
+  end interface
+
+contains
+
+  function any_vector1(vec) result(this)
+    class(*), intent(in) :: vec(:)
+    type(any_vector) :: this
+    allocate(this%vec, source=vec)
+  end function
+
+end module
+
+program main
+
+  use any_vector_type
+  implicit none
+
+  class(*), allocatable :: x
+  character(*), parameter :: vec(2) = ['foo','bar']
+  integer :: vec1(3) = [7,8,9]
+
+  call foo1
+  call foo2
+  call foo3
+  call foo4
+
+contains
+
+  subroutine foo1 ! This always worked
+    allocate (any_vector :: x)
+    select type (x)
+      type is (any_vector)
+        x = any_vector(vec)
+    end select
+    call bar(1)
+    deallocate (x)
+  end
+
+  subroutine foo2 ! Failure found during diagnosis
+    x = any_vector (vec)
+    call bar(2)
+    deallocate (x)
+  end
+
+  subroutine foo3 ! Original failure
+    allocate (x, source = any_vector (vec))
+    call bar(3)
+    deallocate (x)
+  end
+
+  subroutine foo4 ! This always worked
+    allocate (x, source = any_vector (vec1))
+    call bar(4)
+    deallocate (x)
+  end
+
+  subroutine bar (stop_flag)
+    integer :: stop_flag
+    select type (x)
+      type is (any_vector)
+        select type (xvec => x%vec)
+          type is (character(*))
+            if (any(xvec /= vec)) stop stop_flag
+          type is (integer)
+            if (any(xvec /= (vec1))) stop stop_flag
+        end select
+    end select
+  end
+end program