OpenCores
URL https://opencores.org/ocsvn/openrisc_2011-10-31/openrisc_2011-10-31/trunk

Subversion Repositories openrisc_2011-10-31

[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [altreturn_5.f90] - Blame information for rev 154

Details | Compare with Previous | View Log

Line No. Rev Author Line
1 149 jeremybenn
! { dg-do run }
2
! Tests the fix for PR31483, in which dummy argument procedures
3
! produced an ICE if they had an alternate return.
4
!
5
! Contributed by Mathias Fröhlich 
6
 
7
      SUBROUTINE R (i, *, *)
8
      INTEGER i
9
      RETURN i
10
      END
11
 
12
      SUBROUTINE PHLOAD (READER, i, res)
13
      IMPLICIT NONE
14
      EXTERNAL         READER
15
      integer i
16
      character(3) res
17
      CALL READER (i, *1, *2)
18
 1    res = "one"
19
      return
20
 2    res = "two"
21
      return
22
      END
23
 
24
      EXTERNAL R
25
      character(3) res
26
      call PHLOAD (R, 1, res)
27
      if (res .ne. "one") call abort ()
28
      CALL PHLOAD (R, 2, res)
29
      if (res .ne. "two") call abort ()
30
      END

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.