https://gcc.gnu.org/g:5ec7193faa7a5a78dd5382aec220a49f4a76a976

commit r14-11309-g5ec7193faa7a5a78dd5382aec220a49f4a76a976
Author: Harald Anlauf <anl...@gmx.de>
Date:   Fri Feb 7 21:21:10 2025 +0100

    Fortran: fix initialization of allocatable non-deferred character [PR59252]
    
            PR fortran/59252
    
    gcc/fortran/ChangeLog:
    
            * trans-expr.cc (gfc_trans_subcomponent_assign): Initialize
            allocatable non-deferred character with NULL properly.
    
    gcc/testsuite/ChangeLog:
    
            * gfortran.dg/allocatable_char_1.f90: New test.
    
    (cherry picked from commit 818c36a85e3faec5442eb26799bfa3bba7764b36)

Diff:
---
 gcc/fortran/trans-expr.cc                        |  8 +++-
 gcc/testsuite/gfortran.dg/allocatable_char_1.f90 | 47 ++++++++++++++++++++++++
 2 files changed, 53 insertions(+), 2 deletions(-)

diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc
index 601cc546d438..f6de2227675b 100644
--- a/gcc/fortran/trans-expr.cc
+++ b/gcc/fortran/trans-expr.cc
@@ -9407,9 +9407,13 @@ gfc_trans_subcomponent_assign (tree dest, gfc_component 
* cm,
       tmp = gfc_trans_alloc_subarray_assign (tmp, cm, expr);
       gfc_add_expr_to_block (&block, tmp);
     }
-  else if (init && cm->attr.allocatable && expr->expr_type == EXPR_NULL)
+  else if (cm->attr.allocatable && expr->expr_type == EXPR_NULL
+          && (init
+              || (cm->ts.type == BT_CHARACTER
+                  && !(cm->ts.deferred || cm->attr.pdt_string))))
     {
-      /* NULL initialization for allocatable components.  */
+      /* NULL initialization for allocatable components.
+        Deferred-length character is dealt with later.  */
       gfc_add_modify (&block, dest, fold_convert (TREE_TYPE (dest),
                                                  null_pointer_node));
     }
diff --git a/gcc/testsuite/gfortran.dg/allocatable_char_1.f90 
b/gcc/testsuite/gfortran.dg/allocatable_char_1.f90
new file mode 100644
index 000000000000..1d6c25c4942d
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/allocatable_char_1.f90
@@ -0,0 +1,47 @@
+! { dg-do run }
+! { dg-additional-options "-fdump-tree-original" }
+!
+! PR fortran/59252
+
+module mod
+  implicit none
+
+  type t1
+     character(256), allocatable :: label
+  end type t1
+
+  type t2
+     type(t1),       allocatable :: appv(:)
+  end type t2
+
+contains
+  subroutine construct(res)
+    type(t2), allocatable, intent(inout) :: res
+    if (.not. allocated(res)) allocate(res)
+  end subroutine construct
+
+  subroutine construct_appv(appv)
+    type(t1), allocatable, intent(inout) :: appv(:)
+    if (.not. allocated(appv)) allocate(appv(20))
+  end subroutine construct_appv
+
+  type(t1) function foo () result (res)
+  end function foo
+end module mod
+
+program testy
+  use mod
+  implicit none
+  type(t2), allocatable :: res
+  type(t1)              :: s
+
+  ! original test from pr59252
+  call construct     (res)
+  call construct_appv(res%appv)
+  deallocate (res)
+
+  ! related test from pr118747 comment 2:
+  s = foo ()
+end program testy
+
+! { dg-final { scan-tree-dump-not "__builtin_memmove" "original" } }

Reply via email to