aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr114959.f90
blob5cc3c052c1dbfb15c2da3df7010659e3cec13a3e
1 ! { dg-do compile }
2 ! { dg-options "-fdump-tree-original" }
4 ! Fix the regression caused by r14-9752 (fix for PR112407)
5 ! Contributed by Orion Poplawski <orion@nwra.com>
6 ! Problem isolated by Jakub Jelinek <jakub@gcc.gnu.org> and further
7 ! reduced here.
9 module m
10 type :: smoother_type
11 integer :: i
12 end type
13 type :: onelev_type
14 class(smoother_type), allocatable :: sm
15 class(smoother_type), allocatable :: sm2a
16 end type
17 contains
18 subroutine save_smoothers(level,save1, save2)
19 Implicit None
20 type(onelev_type), intent(inout) :: level
21 class(smoother_type), allocatable , intent(inout) :: save1, save2
22 integer(4) :: info
24 info = 0
25 ! r14-9752 causes the 'stat' declaration from the first ALLOCATE statement
26 ! to disappear, which triggers an ICE in gimplify_var_or_parm_decl. The
27 ! second ALLOCATE statement has to be present for the ICE to occur.
28 allocate(save1, mold=level%sm,stat=info)
29 allocate(save2, mold=level%sm2a,stat=info)
30 end subroutine save_smoothers
31 end module m
32 ! Two 'stat's from the allocate statements and two from the final wrapper.
33 ! { dg-final { scan-tree-dump-times "integer\\(kind..\\) stat" 4 "original" } }