2018-09-30 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_decl_2.f90
blobf1f7e098de6c167749d095c01ad7e46bb7e32772
1 ! { dg-do run }
2 ! Various runtime tests of PROCEDURE declarations.
3 ! Contributed by Janus Weil <jaydub66@gmail.com>
5 module m
7 use ISO_C_BINDING
9 abstract interface
10 subroutine csub() bind(c)
11 end subroutine csub
12 end interface
14 integer, parameter :: ckind = C_FLOAT_COMPLEX
15 abstract interface
16 function stub() bind(C)
17 import ckind
18 complex(ckind) stub
19 end function
20 end interface
22 procedure():: mp1
23 procedure(real), private:: mp2
24 procedure(mfun), public:: mp3
25 procedure(csub), public, bind(c) :: c, d
26 procedure(csub), public, bind(c, name="myB") :: b
27 procedure(stub), bind(C) :: e
29 contains
31 real function mfun(x,y)
32 real x,y
33 mfun=4.2
34 end function
36 subroutine bar(a,b)
37 implicit none
38 interface
39 subroutine a()
40 end subroutine a
41 end interface
42 optional :: a
43 procedure(a), optional :: b
44 end subroutine bar
46 subroutine bar2(x)
47 abstract interface
48 character function abs_fun()
49 end function
50 end interface
51 procedure(abs_fun):: x
52 end subroutine
55 end module
58 program p
59 implicit none
61 abstract interface
62 subroutine abssub(x)
63 real x
64 end subroutine
65 end interface
67 integer i
68 real r
70 procedure(integer):: p1
71 procedure(fun):: p2
72 procedure(abssub):: p3
73 procedure(sub):: p4
74 procedure():: p5
75 procedure(p4):: p6
76 procedure(integer) :: p7
78 i=p1()
79 if (i /= 5) STOP 1
80 i=p2(3.1)
81 if (i /= 3) STOP 2
82 r=4.2
83 call p3(r)
84 if (abs(r-5.2)>1e-6) STOP 3
85 call p4(r)
86 if (abs(r-3.7)>1e-6) STOP 4
87 call p5()
88 call p6(r)
89 if (abs(r-7.4)>1e-6) STOP 5
90 i=p7(4)
91 if (i /= -8) STOP 6
92 r=dummytest(p3)
93 if (abs(r-2.1)>1e-6) STOP 7
95 contains
97 integer function fun(x)
98 real x
99 fun=7
100 end function
102 subroutine sub(x)
103 real x
104 end subroutine
106 real function dummytest(dp)
107 procedure(abssub):: dp
108 real y
109 y=1.1
110 call dp(y)
111 dummytest=y
112 end function
114 end program p
117 integer function p1()
118 p1 = 5
119 end function
121 integer function p2(x)
122 real x
123 p2 = int(x)
124 end function
126 subroutine p3(x)
127 real :: x
128 x=x+1.0
129 end subroutine
131 subroutine p4(x)
132 real :: x
133 x=x-1.5
134 end subroutine
136 subroutine p5()
137 end subroutine
139 subroutine p6(x)
140 real :: x
141 x=x*2.
142 end subroutine
144 function p7(x)
145 implicit none
146 integer :: x, p7
147 p7 = x*(-2)
148 end function