gfortran.h (gfc_typebound_proc): New struct.
[gcc.git] / gcc / testsuite / gfortran.dg / typebound_proc_2.f90
1 ! { dg-do compile }
2 ! { dg-options "-std=f95" }
3
4 ! Type-bound procedures
5 ! Test that F95 does not allow type-bound procedures
6
7 MODULE testmod
8 IMPLICIT NONE
9
10 TYPE t
11 INTEGER :: x
12 CONTAINS ! { dg-error "Fortran 2003" }
13 PROCEDURE proc1 ! { dg-error "Fortran 2003" }
14 PROCEDURE :: proc2 => p2 ! { dg-error "Fortran 2003" }
15 END TYPE t
16
17 CONTAINS
18
19 SUBROUTINE proc1 (me)
20 IMPLICIT NONE
21 TYPE(t1) :: me
22 END SUBROUTINE proc1
23
24 REAL FUNCTION proc2 (me, x)
25 IMPLICIT NONE
26 TYPE(t1) :: me
27 REAL :: x
28 proc2 = x / 2
29 END FUNCTION proc2
30
31 END MODULE testmod
32
33 ! { dg-final { cleanup-modules "testmod" } }
34 ! FIXME: Remove not-yet-implemented error when implemented.
35 ! { dg-excess-errors "no IMPLICIT type|not yet implemented" }