Update ChangeLog and version files for release
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_lib_realloc_1.f90
blobc55507b582122cb9916f0c61e41d199b451d6c66
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original -fcoarray=lib" }
4 ! PR fortran/52052
6 ! Test that for CAF components _gfortran_caf_deregister is called
7 ! Test that norealloc happens for CAF components during assignment
9 module m
10 type t
11 integer, allocatable :: CAF[:]
12 integer, allocatable :: ii
13 end type t
14 end module m
16 subroutine foo()
17 use m
18 type(t) :: x,y
19 if (allocated(x%caf)) call abort()
20 x = y
21 end
23 ! For comp%ii: End of scope of x + y (2x) and for the LHS of the assignment (1x)
24 ! { dg-final { scan-tree-dump-times "__builtin_free" 3 "original" } }
26 ! For comp%CAF: End of scope of x + y (2x); no LHS freeing for the CAF in assignment
27 ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister" 2 "original" } }
29 ! Only malloc "ii":
30 ! { dg-final { scan-tree-dump-times "__builtin_malloc" 1 "original" } }
32 ! But copy "ii" and "CAF":
33 ! { dg-final { scan-tree-dump-times "__builtin_memcpy|= MEM" 2 "original" } }