aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / altreturn_5.f90
blob1a4b22d8888a28d300c796197c8ceb9329cfc40b
1 ! { dg-do run }
2 ! { dg-options "-std=gnu" }
4 ! Tests the fix for PR31483, in which dummy argument procedures
5 ! produced an ICE if they had an alternate return.
7 ! Contributed by Mathias Fröhlich <M.Froehlich@science-computing.de>
9 SUBROUTINE R (i, *, *)
10 INTEGER i
11 RETURN i
12 END
14 SUBROUTINE PHLOAD (READER, i, res)
15 IMPLICIT NONE
16 EXTERNAL READER
17 integer i
18 character(3) res
19 CALL READER (i, *1, *2)
20 1 res = "one"
21 return
22 2 res = "two"
23 return
24 END
26 EXTERNAL R
27 character(3) res
28 call PHLOAD (R, 1, res)
29 if (res .ne. "one") STOP 1
30 CALL PHLOAD (R, 2, res)
31 if (res .ne. "two") STOP 2
32 END