aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/protected_10.f90
blob: 1bb20983e944982ddb4f2dcaa6631c5536039ccd (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
! { dg-do compile }
! PR fortran/83135 - fix checking of protected variables in submodules

module mod1
  implicit none
  private
  integer, protected, public :: xx = 42
  public :: set_xx
  public :: echo1_xx, echo2_xx
  interface
     module subroutine echo1_xx()
     end subroutine echo1_xx
     module subroutine echo2_xx()
     end subroutine echo2_xx
  end interface
contains
  subroutine set_xx(arg)
    integer, intent(in) :: arg
    xx = arg    ! valid (it is host_associated)
  end
end module
!
submodule (mod1) s1mod1
  implicit none
contains
  module subroutine echo1_xx()
    xx = 11     ! valid (it is from the ancestor)
    write(*,*) "xx=", xx
  end subroutine echo1_xx
end submodule
!
submodule (mod1:s1mod1) s2mod1
  implicit none
contains
  module subroutine echo2_xx()
    xx = 12     ! valid (it is from the ancestor)
    write(*,*) "xx=", xx
  end subroutine echo2_xx
end submodule
!
module mod2
  use mod1
  implicit none
  integer, protected, public :: yy = 43
  interface
     module subroutine echo_xx()
     end subroutine echo_xx
  end interface
contains
  subroutine bla
!   xx = 999    ! detected, leads to fatal error
  end
end module
!
submodule (mod2) smod2
  implicit none
contains
  module subroutine echo_xx ()
    xx = 10     ! { dg-error "is PROTECTED" }
    write(*,*) "xx=", xx
    yy = 22     ! valid (it is from the ancestor)
  end
end submodule
!
program test_protected
  use mod1
  use mod2
  implicit none
  write(*,*) "xx=", xx
  call set_xx(88)
  write(*,*) "xx=", xx
  call echo_xx
  call echo1_xx
  call echo2_xx
end program