1! { dg-do compile }
2!
3! PR 39630: [F03] Procedure Pointer Components with PASS
4!
5! Contributed by Janus Weil <janus@gcc.gnu.org>
6
7module m
8
9 type :: t0
10  procedure() :: p0  ! { dg-error "POINTER attribute is required for procedure pointer component" }
11 end type
12
13 type :: t1
14  integer :: i
15  procedure(foo1), pointer :: f1  ! { dg-error "must be scalar" }
16 end type
17
18 type :: t2
19  integer :: i
20  procedure(foo2), pointer :: f2  ! { dg-error "may not have the POINTER attribute" }
21 end type
22
23 type :: t3
24  integer :: i
25  procedure(foo3), pointer :: f3  ! { dg-error "may not be ALLOCATABLE" }
26 end type
27
28 type :: t4
29   procedure(),     pass(x), pointer :: f4  ! { dg-error "NOPASS or explicit interface required" }
30   procedure(real), pass(y), pointer :: f5  ! { dg-error "NOPASS or explicit interface required" }
31   procedure(foo6), pass(c), pointer :: f6  ! { dg-error "has no argument" }
32 end type
33
34 type :: t7
35   procedure(foo7), pass, pointer :: f7  ! { dg-error "must have at least one argument" }
36 end type
37
38 type :: t8
39   procedure(foo8), pass, pointer :: f8  ! { dg-error "must be of the derived type" }
40 end type
41
42contains
43
44 subroutine foo1 (x1,y1)
45  type(t1) :: x1(:)
46  type(t1) :: y1
47 end subroutine
48
49 subroutine foo2 (x2,y2)
50  type(t2),pointer :: x2
51  type(t2) :: y2
52 end subroutine
53
54 subroutine foo3 (x3,y3)
55  type(t3),allocatable :: x3
56  type(t3) :: y3
57 end subroutine
58
59 real function foo6 (a,b)
60   real :: a,b
61   foo6 = 1.
62 end function
63
64 integer function foo7 ()
65   foo7 = 2
66 end function
67
68 character function foo8 (i)
69   integer :: i
70 end function
71
72end module m
73