2017-02-20 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / submodule_25.f08
blob0581ce3ca7645ccf939250c50d81acf6dbff0e57
1 ! { dg-do compile }
2 ! Test the fix for PR79434 in which the PRIVATE attribute of the
3 ! component 'i' of the derived type 't' was not respected in the
4 ! submodule 's_u'.
6 ! Contributed by Reinhold Bader  <Bader@lrz.de>
8 module mod_encap_t
9   implicit none
10   type, public :: t
11     private
12     integer :: i
13   end type
14 end module
15 module mod_encap_u
16   use mod_encap_t
17   type, public, extends(t) :: u
18     private
19     integer :: j
20   end type
21   interface
22     module subroutine fu(this)
23       type(u), intent(inout) :: this
24     end subroutine
25   end interface
26 end module
27 submodule (mod_encap_u) s_u
28 contains
29   module procedure fu
30 !   the following statement should cause the compiler to
31 !   abort, pointing out a private component defined in
32 !   a USED module is being accessed
33     this%i = 2 ! { dg-error "is a PRIVATE component" }
34     this%j = 1
35     write(*, *) 'FAIL'
36   end procedure
37 end submodule
38 program p
39   use mod_encap_u
40   implicit none
41   type(u) :: x
42   call fu(x)
43 end program