2016-10-17 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_ptr_49.f90
blobcb540a4f548f0387ce7eb739e30ab1cb7aeb85fe
1 ! { dg-do compile }
3 ! Tests the fix for PRs 78013 and 61420, both of which gave a
4 ! no IMPLICIT type message for the procedure pointer at assignment.
6 module m
8 implicit none
10 abstract interface
11 function I_f() result( r )
12 real :: r
13 end function I_f
14 end interface
16 type, abstract :: a_t
17 private
18 procedure(I_f), nopass, pointer :: m_f => null()
19 contains
20 private
21 procedure, pass(this), public :: f => get_f
22 end type a_t
24 contains
26 function get_f( this ) result( f_ptr ) ! Error message here.
27 class(a_t), intent(in) :: this
28 procedure(I_f), pointer :: f_ptr
29 f_ptr => this%m_f ! Error here :-)
30 end function get_f
32 end module m
34 module test
35 implicit none
37 type functions
38 contains
39 procedure, nopass :: get_pf => get_it ! Error here
40 end type
42 class(functions), allocatable :: f
44 contains
46 function get_it() ! Error message here.
47 procedure (real), pointer :: get_it
48 end function
50 end module