Merge with trank @ 137446
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_decl_1.f90
blob3e7a3d18fb7f3f992e921f8042a18a0b3c8a208d
1 ! { dg-do compile }
2 ! This tests various error messages for PROCEDURE declarations.
3 ! Contributed by Janus Weil <jaydub66@gmail.com>
5 module m
7 abstract interface
8 subroutine sub()
9 end subroutine
10 subroutine sub2() bind(c)
11 end subroutine
12 end interface
14 procedure(), public, private :: a ! { dg-error "was already specified" }
15 procedure(sub),bind(C) :: a2 ! { dg-error "requires an interface with BIND.C." }
16 procedure(sub2), public, bind(c, name="myEF") :: e, f ! { dg-error "Multiple identifiers provided with single NAME= specifier" }
17 procedure(sub2), bind(C, name=""), pointer :: g ! { dg-error "may not have POINTER attribute" }
19 public:: h
20 procedure(),public:: h ! { dg-error "was already specified" }
22 end module m
25 program prog
27 interface z
28 subroutine z1()
29 end subroutine
30 subroutine z2(a)
31 integer :: a
32 end subroutine
33 end interface
35 procedure(z) :: bar ! { dg-error "may not be generic" }
37 procedure(), allocatable:: b ! { dg-error "PROCEDURE attribute conflicts with ALLOCATABLE attribute" }
38 procedure(), save:: c ! { dg-error "PROCEDURE attribute conflicts with SAVE attribute" }
40 procedure(dcos) :: my1
41 procedure(amax0) :: my2 ! { dg-error "not allowed in PROCEDURE statement" }
43 type t
44 procedure(),pointer:: p ! { dg-error "not yet implemented" }
45 end type
47 real f, x
48 f(x) = sin(x**2)
49 external oo
51 procedure(f) :: q ! { dg-error "may not be a statement function" }
52 procedure(oo) :: p ! { dg-error "must be explicit" }
54 contains
56 subroutine foo(a,c)
57 abstract interface
58 subroutine b() bind(C)
59 end subroutine b
60 end interface
61 procedure(b), bind(c,name="hjj") :: a ! { dg-error "may not have BIND.C. attribute with NAME" }
62 procedure(c),intent(in):: c ! { dg-error "PROCEDURE attribute conflicts with INTENT attribute" }
63 end subroutine foo
65 end program
68 subroutine abc
70 procedure() :: abc2
72 entry abc2(x) ! { dg-error "PROCEDURE attribute conflicts with ENTRY attribute" }
73 real x
75 end subroutine