* combine.c (make_compound_operation) <SUBREG>: If force_to_mode
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_decl_1.f90
blobc7ec4f2f3fc8e376efbefecbd9704da1b3bcda6f
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 contains
24 subroutine abc
25 procedure() :: abc2
26 entry abc2(x) ! { dg-error "PROCEDURE attribute conflicts with ENTRY attribute" }
27 real x
28 end subroutine
30 end module m
32 program prog
34 interface z
35 subroutine z1()
36 end subroutine
37 subroutine z2(a)
38 integer :: a
39 end subroutine
40 end interface
42 procedure(z) :: bar ! { dg-error "may not be generic" }
44 procedure(), allocatable:: b ! { dg-error "PROCEDURE attribute conflicts with ALLOCATABLE attribute" }
45 procedure(), save:: c ! { dg-error "PROCEDURE attribute conflicts with SAVE attribute" }
47 procedure(dcos) :: my1
48 procedure(amax0) :: my2 ! { dg-error "not allowed in PROCEDURE statement" }
50 real f, x
51 f(x) = sin(x**2)
52 external oo
54 procedure(f) :: q ! { dg-error "may not be a statement function" }
55 procedure(oo) :: p ! { dg-error "must be explicit" }
57 procedure ( ) :: r
58 procedure ( up ) :: s ! { dg-error "must be explicit" }
60 procedure(t) :: t ! { dg-error "may not be used as its own interface" }
62 call s
64 contains
66 subroutine foo(a,c) ! { dg-error "PROCEDURE attribute conflicts with INTENT attribute" }
67 abstract interface
68 subroutine b() bind(C)
69 end subroutine b
70 end interface
71 procedure(b), bind(c,name="hjj") :: a ! { dg-error "may not have BIND.C. attribute with NAME" }
72 procedure(b),intent(in):: c
73 end subroutine foo
75 end program