aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / func_assign_3.f90
blob1d4ff15f07b95a1fc3354d5f50455f2ca0ee9ac0
1 ! { dg-do run }
2 ! Tests the fix for PR40646 in which the assignment would cause an ICE.
4 ! Contributed by Charlie Sharpsteen <chuck@sharpsteen.net>
5 ! http://gcc.gnu.org/ml/fortran/2009-07/msg00010.html
6 ! and reported by Tobias Burnus <burnus@gcc,gnu.org>
8 module bugTestMod
9 implicit none
10 type:: boundTest
11 contains
12 procedure, nopass:: test => returnMat
13 end type boundTest
14 contains
15 function returnMat( a, b ) result( mat )
16 integer:: a, b, i
17 double precision, dimension(a,b):: mat
18 mat = dble (reshape ([(i, i = 1, a * b)],[a,b]))
19 return
20 end function returnMat
21 end module bugTestMod
23 program bugTest
24 use bugTestMod
25 implicit none
26 integer i
27 double precision, dimension(2,2):: testCatch
28 type( boundTest ):: testObj
29 testCatch = testObj%test(2,2) ! This would cause an ICE
30 if (any (testCatch .ne. dble (reshape ([(i, i = 1, 4)],[2,2])))) STOP 1
31 end program bugTest