OSDN Git Service

2006-11-28 Paul Thomas <pault@gcc.gnu.org>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / derived_function_interface_1.f90
1 ! { dg-compile }
2 ! Tests the fix for PR29634, in which an ICE would occur in the
3 ! interface declaration of a function with an 'old-style' type
4 ! declaration.  When fixed, it was found that the error message
5 ! was not very helpful - this was fixed.
6 !
7 ! Contributed by Francois-Xavier Coudert  <fxcoudert@gcc.gnu.org>
8 !
9 type(foo) function ext_fun()
10   type foo
11     integer :: i
12   end type foo
13   ext_fun%i = 1
14 end function ext_fun
15
16   type foo
17     integer :: i
18   end type foo
19
20   interface fun_interface
21     type(foo) function fun()
22     end function fun
23   end interface
24
25   interface ext_fun_interface
26     type(foo) function ext_fun()
27     end function ext_fun
28   end interface
29
30   type(foo) :: x
31
32   x = ext_fun ()
33   print *, x%i
34
35 contains
36
37   type(foo) function fun() ! { dg-error "already has an explicit interface" }
38   end function fun  ! { dg-error "Expecting END PROGRAM" }
39
40 end ! { dg-warning "CONTAINS statement without FUNCTION or SUBROUTINE statement" }