aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90
diff options
context:
space:
mode:
authorBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
committerBen Cheng <bccheng@google.com>2014-03-25 22:37:19 -0700
commit1bc5aee63eb72b341f506ad058502cd0361f0d10 (patch)
treec607e8252f3405424ff15bc2d00aa38dadbb2518 /gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90
parent283a0bf58fcf333c58a2a92c3ebbc41fb9eb1fdb (diff)
downloadtoolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.gz
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.tar.bz2
toolchain_gcc-1bc5aee63eb72b341f506ad058502cd0361f0d10.zip
Initial checkin of GCC 4.9.0 from trunk (r208799).
Change-Id: I48a3c08bb98542aa215912a75f03c0890e497dba
Diffstat (limited to 'gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f9067
1 files changed, 67 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90
new file mode 100644
index 000000000..3a8bc3bf7
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/c_by_val_5.f90
@@ -0,0 +1,67 @@
+! { dg-do run }
+! Overwrite -pedantic setting:
+! { dg-options "-Wall" }
+!
+! Tests the fix for PR31668, in which %VAL was rejected for
+! module and internal procedures.
+!
+
+subroutine bmp_write(nx)
+ implicit none
+ integer, value :: nx
+ if(nx /= 10) call abort()
+ nx = 11
+ if(nx /= 11) call abort()
+end subroutine bmp_write
+
+module x
+ implicit none
+ ! The following interface does in principle
+ ! not match the procedure (missing VALUE attribute)
+ ! However, this occures in real-world code calling
+ ! C routines where an interface is better than
+ ! "external" only.
+ interface
+ subroutine bmp_write(nx)
+ integer, value :: nx
+ end subroutine bmp_write
+ end interface
+contains
+ SUBROUTINE Grid2BMP(NX)
+ INTEGER, INTENT(IN) :: NX
+ if(nx /= 10) call abort()
+ call bmp_write(%val(nx))
+ if(nx /= 10) call abort()
+ END SUBROUTINE Grid2BMP
+END module x
+
+! The following test is possible and
+! accepted by other compilers, but
+! does not make much sense.
+! Either one uses VALUE then %VAL is
+! not needed or the function will give
+! wrong results.
+!
+!subroutine test()
+! implicit none
+! integer :: n
+! n = 5
+! if(n /= 5) call abort()
+! call test2(%VAL(n))
+! if(n /= 5) call abort()
+! contains
+! subroutine test2(a)
+! integer, value :: a
+! if(a /= 5) call abort()
+! a = 2
+! if(a /= 2) call abort()
+! end subroutine test2
+!end subroutine test
+
+program main
+ use x
+ implicit none
+! external test
+ call Grid2BMP(10)
+! call test()
+end program main