URL
https://opencores.org/ocsvn/openrisc/openrisc/trunk
Subversion Repositories openrisc
[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [block_7.f08] - Rev 694
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-std=f2008 -fall-intrinsics" }! Check for correct placement (on the stack) of local variables with BLOCK! and recursive container procedures.RECURSIVE SUBROUTINE myproc (i)INTEGER, INTENT(IN) :: i! Wrap the block up in some other construct so we see this doesn't mess! things up, either.DOBLOCKINTEGER :: xx = iIF (i > 0) CALL myproc (i - 1)IF (x /= i) CALL abort ()END BLOCKEXITEND DOEND SUBROUTINE myprocPROGRAM mainCALL myproc (42)END PROGRAM main
