summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/bind_c_usage_14.f03
diff options
context:
space:
mode:
authorupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
committerupstream source tree <ports@midipix.org>2015-03-15 20:14:05 -0400
commit554fd8c5195424bdbcabf5de30fdc183aba391bd (patch)
tree976dc5ab7fddf506dadce60ae936f43f58787092 /gcc/testsuite/gfortran.dg/bind_c_usage_14.f03
downloadcbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.bz2
cbb-gcc-4.6.4-554fd8c5195424bdbcabf5de30fdc183aba391bd.tar.xz
obtained gcc-4.6.4.tar.bz2 from upstream website;upstream
verified gcc-4.6.4.tar.bz2.sig; imported gcc-4.6.4 source tree from verified upstream tarball. downloading a git-generated archive based on the 'upstream' tag should provide you with a source tree that is binary identical to the one extracted from the above tarball. if you have obtained the source via the command 'git clone', however, do note that line-endings of files in your working directory might differ from line-endings of the respective files in the upstream repository.
Diffstat (limited to 'gcc/testsuite/gfortran.dg/bind_c_usage_14.f03')
-rw-r--r--gcc/testsuite/gfortran.dg/bind_c_usage_14.f03115
1 files changed, 115 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/bind_c_usage_14.f03 b/gcc/testsuite/gfortran.dg/bind_c_usage_14.f03
new file mode 100644
index 000000000..2d6726af8
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/bind_c_usage_14.f03
@@ -0,0 +1,115 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+!
+! PR fortran/34079
+! Bind(C) procedures shall have no character length
+! dummy and actual arguments.
+!
+
+! SUBROUTINES
+
+subroutine sub1noiso(a, b)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+end subroutine sub1noiso
+
+subroutine sub2(a, b) bind(c)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+end subroutine sub2
+
+! SUBROUTINES with ENTRY
+
+subroutine sub3noiso(a, b)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+entry sub3noisoEntry(x,y,z)
+ x = 'd'
+end subroutine sub3noiso
+
+subroutine sub4iso(a, b) bind(c)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+entry sub4isoEntry(x,y,z)
+ x = 'd'
+end subroutine sub4iso
+
+subroutine sub5iso(a, b) bind(c)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+entry sub5noIsoEntry(x,y,z)
+ x = 'd'
+end subroutine sub5iso
+
+subroutine sub6NoIso(a, b)
+ use iso_c_binding
+ implicit none
+ character(len=1,kind=c_char) :: a(*), b
+ character(len=1,kind=c_char):: x,z
+ integer(c_int) :: y
+ value :: b
+ print *, a(1:2), b
+entry sub6isoEntry(x,y,z)
+ x = 'd'
+end subroutine sub6NoIso
+
+! The subroutines (including entry) should have
+! only a char-length parameter if they are not bind(C).
+!
+! { dg-final { scan-tree-dump "sub1noiso \\(\[^.\]*a, \[^.\]*b, \[^.\]*_a, \[^.\]*_b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub2 \\(\[^.\]*a, \[^.\]*b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub3noiso \\(\[^.\]*a, \[^.\]*b, \[^.\]*_a, \[^.\]*_b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub3noisoentry \\(\[^.\]*x, \[^.\]*y, \[^.\]*z, \[^.\]*_x, \[^.\]*_z\\)" "original" } }
+! { dg-final { scan-tree-dump "sub4iso \\(\[^.\]*a, \[^.\]*b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub4isoentry \\(\[^.\]*x, \[^.\]*y, \[^.\]*z, \[^.\]*_x, \[^.\]*_z\\)" "original" } }
+! { dg-final { scan-tree-dump "sub5iso \\(\[^.\]*a, \[^.\]*b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub5noisoentry \\(\[^.\]*x, \[^.\]*y, \[^.\]*z, \[^.\]*_x, \[^.\]*_z\\)" "original" } }
+! { dg-final { scan-tree-dump "sub6noiso \\(\[^.\]*a, \[^.\]*b, \[^.\]*_a, \[^.\]*_b\\)" "original" } }
+! { dg-final { scan-tree-dump "sub6isoentry \\(\[^.\]*x, \[^.\]*y, \[^.\]*z, \[^.\]*_x, \[^.\]*_z\\)" "original" } }
+
+! The master functions should have always a length parameter
+! to ensure sharing a parameter between bind(C) and non-bind(C) works
+!
+! { dg-final { scan-tree-dump "master.0.sub3noiso \\(\[^.\]*__entry, \[^.\]*z, \[^.\]*y, \[^.\]*x, \[^.\]*b, \[^.\]*a, \[^.\]*_z, \[^.\]*_x, \[^.\]*_b, \[^.\]*_a\\)" "original" } }
+! { dg-final { scan-tree-dump "master.1.sub4iso \\(\[^.\]*__entry, \[^.\]*z, \[^.\]*y, \[^.\]*x, \[^.\]*b, \[^.\]*a, \[^.\]*_z, \[^.\]*_x, \[^.\]*_b, \[^.\]*_a\\)" "original" } }
+! { dg-final { scan-tree-dump "master.2.sub5iso \\(\[^.\]*__entry, \[^.\]*z, \[^.\]*y, \[^.\]*x, \[^.\]*b, \[^.\]*a, \[^.\]*_z, \[^.\]*_x, \[^.\]*_b, \[^.\]*_a\\)" "original" } }
+! { dg-final { scan-tree-dump "master.3.sub6noiso \\(\[^.\]*__entry, \[^.\]*z, \[^.\]*y, \[^.\]*x, \[^.\]*b, \[^.\]*a, \[^.\]*_z, \[^.\]*_x, \[^.\]*_b, \[^.\]*_a\\)" "original" } }
+
+! Thus, the master functions need to be called with length arguments
+! present
+!
+! { dg-final { scan-tree-dump "master.0.sub3noiso .0, 0B, 0B, 0B, b, a, 0, 0, 1, 1\\);" "original" } }
+! { dg-final { scan-tree-dump "master.0.sub3noiso .1, z, y, x, 0B, 0B, 1, 1, 0, 0\\);" "original" } }
+! { dg-final { scan-tree-dump "master.1.sub4iso .0, 0B, 0B, 0B, b, a, 0, 0, 1, 1\\);" "original" } }
+! { dg-final { scan-tree-dump "master.1.sub4iso .1, z, y, x, 0B, 0B, 1, 1, 0, 0\\);" "original" } }
+! { dg-final { scan-tree-dump "master.2.sub5iso .0, 0B, 0B, 0B, b, a, 0, 0, 1, 1\\);" "original" } }
+! { dg-final { scan-tree-dump "master.2.sub5iso .1, z, y, x, 0B, 0B, 1, 1, 0, 0\\);" "original" } }
+! { dg-final { scan-tree-dump "master.3.sub6noiso .0, 0B, 0B, 0B, b, a, 0, 0, 1, 1\\);" "original" } }
+! { dg-final { scan-tree-dump "master.3.sub6noiso .1, z, y, x, 0B, 0B, 1, 1, 0, 0\\);" "original" } }
+
+! { dg-final { cleanup-tree-dump "original" } }