URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [nested_modules_3.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }!! This tests the improved version of the patch for PR16861. Testing! after committing the first version, revealed that this test did! not work but was not regtested for, either.!! Contributed by Paul Thomas <pault@gcc.gnu.org>!MODULE fooTYPE type1INTEGER i1END TYPE type1END MODULEMODULE barCONTAINSSUBROUTINE sub1 (x, y)USE fooTYPE (type1) :: xINTEGER :: y(x%i1)y = 1END SUBROUTINE SUB1SUBROUTINE sub2 (u, v)USE fooTYPE (type1) :: uINTEGER :: v(u%i1)v = 2END SUBROUTINE SUB2END MODULEMODULE foobarUSE fooUSE barCONTAINSSUBROUTINE sub3 (s, t)USE fooTYPE (type1) :: sINTEGER :: t(s%i1)t = 3END SUBROUTINE SUB3END MODULE foobarPROGRAM use_foobarUSE fooUSE foobarINTEGER :: j(3) = 0TYPE (type1) :: zz%i1 = 3CALL sub1 (z, j)z%i1 = 2CALL sub2 (z, j)z%i1 = 1CALL sub3 (z, j)IF (ALL (j.ne.(/3,2,1/))) CALL abort ()END PROGRAM use_foobar! { dg-final { cleanup-modules "foo bar foobar" } }
