OSDN Git Service

2010-06-07 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / dummy_procedure_1.f90
1 ! { dg-do compile }
2 ! Test the patch for PR25098, where passing a variable as an
3 ! actual argument to a formal argument that is a procedure
4 ! went undiagnosed.
5 !
6 ! Based on contribution by Joost VandeVondele  <jv244@cam.ac.uk>
7 !
8 integer function y()
9   y = 1
10 end
11 integer function z()
12   z = 1
13 end
14
15 module m1
16 contains
17   subroutine s1(f)
18     interface
19       function f()
20         integer f
21       end function f
22     end interface
23   end subroutine s1
24   subroutine s2(x)
25     integer :: x
26   end subroutine
27 end module m1
28
29   use m1
30   external y
31   interface
32    function x()
33      integer x
34    end function x
35   end interface
36
37   integer :: i, y, z
38   i=1
39   call s1(i) ! { dg-error "Expected a procedure for argument" }
40   call s1(w) ! { dg-error "not allowed as an actual argument" }
41   call s1(x) ! explicit interface
42   call s1(y) ! declared external
43   call s1(z) ! { dg-error "Expected a procedure for argument" }
44   call s2(x) ! { dg-error "Invalid procedure argument" }
45 contains
46   integer function w()
47     w = 1
48   end function w
49 end
50
51 ! { dg-final { cleanup-modules "m1" } }