re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / dummy_procedure_4.f90
blob8c1e55417e00474ca8f5149880ab3501da81438b
1 ! { dg-do compile }
3 ! PR 46067: [F03] invalid procedure pointer assignment not detected
5 ! Contributed by Janus Weil <janus@gcc.gnu.org>
7 module m
9 type test_type
10 integer :: id = 1
11 end type
13 contains
15 real function fun1 (t,x)
16 real, intent(in) :: x
17 type(test_type) :: t
18 print *," id = ", t%id
19 fun1 = cos(x)
20 end function
22 end module
25 use m
26 implicit none
28 call test (fun1) ! { dg-error "Interface mismatch in dummy procedure" }
30 contains
32 subroutine test(proc)
33 interface
34 real function proc(t,x)
35 import :: test_type
36 real, intent(in) :: x
37 class(test_type) :: t
38 end function
39 end interface
40 type(test_type) :: funs
41 real :: r
42 r = proc(funs,0.)
43 print *, " proc(0) ",r
44 end subroutine
46 end