[AArch64] Merge stores of D-register values with different modes
[official-gcc.git] / gcc / testsuite / gfortran.dg / class_allocate_14.f90
blobd2514772a0386da798a040a098d24979db7349dc
1 ! { dg-do run }
2 ! { dg-options "-fdump-tree-original" }
4 ! PR fortran/56845
6 module m
7 type t
8 integer ::a
9 end type t
10 contains
11 subroutine sub
12 type(t), save, allocatable :: x
13 class(t), save,allocatable :: y
14 if (.not. same_type_as(x,y)) STOP 1
15 end subroutine sub
16 subroutine sub2
17 type(t), save, allocatable :: a(:)
18 class(t), save,allocatable :: b(:)
19 if (.not. same_type_as(a,b)) STOP 2
20 end subroutine sub2
21 end module m
23 use m
24 call sub()
25 call sub2()
26 end
28 ! { dg-final { scan-tree-dump-times "static struct __class_m_T_1_0a b = {._data={.data=0B}, ._vptr=&__vtab_m_T};" 1 "original" } }
29 ! { dg-final { scan-tree-dump-times "static struct __class_m_T_a y = {._data=0B, ._vptr=&__vtab_m_T};" 1 "original" } }