1! { dg-do run }
2! { dg-options "-std=f2003 -fall-intrinsics" }
3! PR fortran/23994
4!
5! Test PROTECTED attribute. Within the module everything is allowed.
6! Outside (use-associated): For pointers, their association status
7! may not be changed. For nonpointers, their value may not be changed.
8!
9! Test of a valid code
10
11module protmod
12  implicit none
13  integer, protected          :: a
14  integer, protected, target  :: at
15  integer, protected, pointer :: ap
16contains
17  subroutine setValue()
18    a = 43
19    ap => null()
20    nullify(ap)
21    ap => at
22    ap = 3
23    allocate(ap)
24    ap = 73
25    call increment(a,ap,at)
26    if(a /= 44 .or. ap /= 74 .or. at /= 4) call abort()
27  end subroutine setValue
28  subroutine increment(a1,a2,a3)
29    integer, intent(inout) :: a1, a2, a3
30    a1 = a1 + 1
31    a2 = a2 + 1
32    a3 = a3 + 1
33  end subroutine increment
34end module protmod
35
36program main
37  use protmod
38  implicit none
39  call setValue()
40  if(a /= 44 .or. ap /= 74 .or. at /= 4) call abort()
41  call plus5(ap)
42  if(a /= 44 .or. ap /= 79 .or. at /= 4) call abort()
43  call checkVal(a,ap,at)
44contains
45  subroutine plus5(j)
46    integer, intent(inout) :: j
47    j = j + 5
48  end subroutine plus5
49  subroutine checkVal(x,y,z)
50    integer, intent(in) :: x, y, z
51    if(a /= 44 .or. ap /= 79 .or. at /= 4) call abort()
52  end subroutine
53end program main
54