OSDN Git Service

PR debug/43329
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / proc_ptr_comp_3.f90
1 ! { dg-do compile }
2 !
3 ! PR39630: Fortran 2003: Procedure pointer components.
4 !
5 ! Probing some error messages.
6 !
7 ! Contributed by Janus Weil <janus@gcc.gnu.org>
8
9 implicit none
10
11 interface
12  subroutine sub
13  end subroutine
14 end interface
15
16 external :: aaargh
17
18 type :: t
19   procedure(), pointer, nopass :: ptr1
20   procedure(real), pointer, nopass :: ptr2
21   procedure(sub), pointer, nopass :: ptr3
22   procedure(), pointer, nopass ptr4              ! { dg-error "Expected '::'" }
23   procedure(), pointer, nopass, pointer :: ptr5  ! { dg-error "Duplicate" }
24   procedure, pointer, nopass :: ptr6             ! { dg-error "Syntax error" }
25   procedure(), pointer, nopass :: ptr7 => ptr2   ! { dg-error "requires a NULL" }
26   procedure(), nopass :: ptr8                    ! { dg-error "POINTER attribute is required" }
27   procedure(pp), pointer, nopass :: ptr9         ! { dg-error "declared in a later PROCEDURE statement" }
28   procedure(aaargh), pointer, nopass :: ptr10    ! { dg-error "must be explicit" }
29   real :: y
30 end type t
31
32 type,bind(c) :: bct                   ! { dg-error "BIND.C. derived type" }
33   procedure(), pointer,nopass :: ptr  ! { dg-error "cannot be a member of|may not be C interoperable" }
34 end type bct
35
36 procedure(sub), pointer :: pp
37
38 type(t) :: x
39
40 x%ptr2 => x       ! { dg-error "Invalid procedure pointer assignment" }
41
42 x => x%ptr2       ! { dg-error "Pointer assignment to non-POINTER" }
43
44 print *, x%ptr1() ! { dg-error "attribute conflicts with" }
45 call x%ptr2()     ! { dg-error "attribute conflicts with" }
46 print *,x%ptr3()  ! { dg-error "attribute conflicts with" }
47
48 call x%y          ! { dg-error "Expected type-bound procedure or procedure pointer component" }
49
50 end
51