aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / pr44882.f90
blobac22459dc08a7e2505d4d219ab76e945fb4fdad4
1 ! { dg-do compile }
2 ! { dg-options "-O3 -ffast-math -funroll-loops -w" }
4 SUBROUTINE TRUDGE(KDIR)
5 ! There is a type mismatch here for TRUPAR which caused an ICE
6 COMMON /TRUPAR/ DR(10),V(10,10)
7 DO 110 I=1,NDIR
8 110 DR(I)=V(I,JDIR)
9 END
10 SUBROUTINE TRUSRC(LEAVE)
11 IMPLICIT DOUBLE PRECISION (A-H,O-Z)
12 COMMON /TRUPAR/ DX(10),V(10,10)
13 END