Merged with mainline at revision 128810.
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_decl_2.f90
blob6edc6bd42b37f5886410f96eef5c59a6452a832b
1 ! { dg-do run }
2 ! Various runtime tests of PROCEDURE declarations.
3 ! Contributed by Janus Weil <jaydub66@gmail.com>
5 module m
7 abstract interface
8 subroutine csub() bind(c)
9 end subroutine csub
10 end interface
12 procedure():: mp1
13 procedure(real), private:: mp2
14 procedure(mfun), public:: mp3
15 procedure(csub), public, bind(c) :: c, d
16 procedure(csub), public, bind(c, name="myB") :: b
18 contains
20 real function mfun(x,y)
21 real x,y
22 mfun=4.2
23 end function
25 subroutine bar(a,b)
26 implicit none
27 interface
28 subroutine a()
29 end subroutine a
30 end interface
31 optional :: a
32 procedure(a), optional :: b
33 end subroutine bar
35 end module
38 program p
39 implicit none
41 abstract interface
42 subroutine abssub(x)
43 real x
44 end subroutine
45 end interface
47 integer i
48 real r
50 procedure(integer):: p1
51 procedure(fun):: p2
52 procedure(abssub):: p3
53 procedure(sub):: p4
54 procedure():: p5
55 procedure(p4):: p6
56 procedure(integer) :: p7
58 i=p1()
59 if (i /= 5) call abort()
60 i=p2(3.1)
61 if (i /= 3) call abort()
62 r=4.2
63 call p3(r)
64 if (abs(r-5.2)>1e-6) call abort()
65 call p4(r)
66 if (abs(r-3.7)>1e-6) call abort()
67 call p5()
68 call p6(r)
69 if (abs(r-7.4)>1e-6) call abort()
70 i=p7(4)
71 if (i /= -8) call abort()
72 r=dummytest(p3)
73 if (abs(r-2.1)>1e-6) call abort()
75 contains
77 integer function fun(x)
78 real x
79 fun=7
80 end function
82 subroutine sub(x)
83 real x
84 end subroutine
86 real function dummytest(dp)
87 procedure(abssub):: dp
88 real y
89 y=1.1
90 call dp(y)
91 dummytest=y
92 end function
94 end program p
97 integer function p1()
98 p1 = 5
99 end function
101 integer function p2(x)
102 real x
103 p2 = int(x)
104 end function
106 subroutine p3(x)
107 real,intent(inout):: x
108 x=x+1.0
109 end subroutine
111 subroutine p4(x)
112 real,intent(inout):: x
113 x=x-1.5
114 end subroutine
116 subroutine p5()
117 end subroutine
119 subroutine p6(x)
120 real,intent(inout):: x
121 x=x*2.
122 end subroutine
124 function p7(x)
125 implicit none
126 integer :: x, p7
127 p7 = x*(-2)
128 end function