OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-old/] [gcc-4.2.2/] [gcc/] [testsuite/] [gfortran.dg/] [altreturn_5.f90] - Rev 823

Go to most recent revision | Compare with Previous | Blame | View Log

! { dg-do run }
! Tests the fix for PR31483, in which dummy argument procedures
! produced an ICE if they had an alternate return.
!

      SUBROUTINE R (i, *, *)
      INTEGER i
      RETURN i
      END

      SUBROUTINE PHLOAD (READER, i, res)
      IMPLICIT NONE
      EXTERNAL         READER
      integer i
      character(3) res
      CALL READER (i, *1, *2)
 1    res = "one"
      return
 2    res = "two"
      return
      END

      EXTERNAL R
      character(3) res
      call PHLOAD (R, 1, res)
      if (res .ne. "one") call abort ()
      CALL PHLOAD (R, 2, res)
      if (res .ne. "two") call abort ()
      END

Go to most recent revision | Compare with Previous | Blame | View Log

powered by: WebSVN 2.1.0

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