c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / proc_ptr_comp_7.f90
blob48fd5219e4a32a04479d9867ae26d24486bb77d6
1 ! { dg-do compile }
3 ! PR 40089: Public type with public component which has a private type
5 ! Original test case by Juergen Reuter <reuter@physik.uni-freiburg.de>
6 ! Adapted by Janus Weil <janus@gcc.gnu.org>
8 module m
10 implicit none
11 private
13 public :: public_t
15 type :: private_t
16 integer :: i
17 end type
19 type :: public_t
20 type(private_t), pointer :: public_comp_with_private_type
21 procedure(ifc) , nopass, pointer :: ppc
22 end type
24 abstract interface
25 integer function ifc ()
26 end function
27 end interface
29 end module m
31 program test
32 use m
33 implicit none
34 type(public_t) :: x
35 integer :: j
36 j = x%ppc()
37 end