aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/proc_decl_2.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/proc_decl_2.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/proc_decl_2.f90')
-rw-r--r--gcc-4.9/gcc/testsuite/gfortran.dg/proc_decl_2.f90148
1 files changed, 148 insertions, 0 deletions
diff --git a/gcc-4.9/gcc/testsuite/gfortran.dg/proc_decl_2.f90 b/gcc-4.9/gcc/testsuite/gfortran.dg/proc_decl_2.f90
new file mode 100644
index 000000000..97e06148e
--- /dev/null
+++ b/gcc-4.9/gcc/testsuite/gfortran.dg/proc_decl_2.f90
@@ -0,0 +1,148 @@
+! { dg-do run }
+! Various runtime tests of PROCEDURE declarations.
+! Contributed by Janus Weil <jaydub66@gmail.com>
+
+module m
+
+ use ISO_C_BINDING
+
+ abstract interface
+ subroutine csub() bind(c)
+ end subroutine csub
+ end interface
+
+ integer, parameter :: ckind = C_FLOAT_COMPLEX
+ abstract interface
+ function stub() bind(C)
+ import ckind
+ complex(ckind) stub
+ end function
+ end interface
+
+ procedure():: mp1
+ procedure(real), private:: mp2
+ procedure(mfun), public:: mp3
+ procedure(csub), public, bind(c) :: c, d
+ procedure(csub), public, bind(c, name="myB") :: b
+ procedure(stub), bind(C) :: e
+
+contains
+
+ real function mfun(x,y)
+ real x,y
+ mfun=4.2
+ end function
+
+ subroutine bar(a,b)
+ implicit none
+ interface
+ subroutine a()
+ end subroutine a
+ end interface
+ optional :: a
+ procedure(a), optional :: b
+ end subroutine bar
+
+ subroutine bar2(x)
+ abstract interface
+ character function abs_fun()
+ end function
+ end interface
+ procedure(abs_fun):: x
+ end subroutine
+
+
+end module
+
+
+program p
+ implicit none
+
+ abstract interface
+ subroutine abssub(x)
+ real x
+ end subroutine
+ end interface
+
+ integer i
+ real r
+
+ procedure(integer):: p1
+ procedure(fun):: p2
+ procedure(abssub):: p3
+ procedure(sub):: p4
+ procedure():: p5
+ procedure(p4):: p6
+ procedure(integer) :: p7
+
+ i=p1()
+ if (i /= 5) call abort()
+ i=p2(3.1)
+ if (i /= 3) call abort()
+ r=4.2
+ call p3(r)
+ if (abs(r-5.2)>1e-6) call abort()
+ call p4(r)
+ if (abs(r-3.7)>1e-6) call abort()
+ call p5()
+ call p6(r)
+ if (abs(r-7.4)>1e-6) call abort()
+ i=p7(4)
+ if (i /= -8) call abort()
+ r=dummytest(p3)
+ if (abs(r-2.1)>1e-6) call abort()
+
+contains
+
+ integer function fun(x)
+ real x
+ fun=7
+ end function
+
+ subroutine sub(x)
+ real x
+ end subroutine
+
+ real function dummytest(dp)
+ procedure(abssub):: dp
+ real y
+ y=1.1
+ call dp(y)
+ dummytest=y
+ end function
+
+end program p
+
+
+integer function p1()
+ p1 = 5
+end function
+
+integer function p2(x)
+ real x
+ p2 = int(x)
+end function
+
+subroutine p3(x)
+ real :: x
+ x=x+1.0
+end subroutine
+
+subroutine p4(x)
+ real :: x
+ x=x-1.5
+end subroutine
+
+subroutine p5()
+end subroutine
+
+subroutine p6(x)
+ real :: x
+ x=x*2.
+end subroutine
+
+function p7(x)
+ implicit none
+ integer :: x, p7
+ p7 = x*(-2)
+end function