re PR fortran/78741 (ICE in gfc_get_symbol_decl, at fortran/trans-decl.c:1534)
[official-gcc.git] / gcc / testsuite / gfortran.dg / protected_2.f90
blob1ea59e356091bc81ce8eddca539f2bc279e3febc
1 ! { dg-do run }
2 ! { dg-options "-std=f2003 " }
3 ! PR fortran/23994
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.
9 ! Test of a valid code
11 module protmod
12 implicit none
13 integer, protected :: a
14 integer, protected, target :: at
15 integer, protected, pointer :: ap
16 contains
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) STOP 1
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
34 end module protmod
36 program main
37 use protmod
38 implicit none
39 call setValue()
40 if(a /= 44 .or. ap /= 74 .or. at /= 4) STOP 2
41 call plus5(ap)
42 if(a /= 44 .or. ap /= 79 .or. at /= 4) STOP 3
43 call checkVal(a,ap,at)
44 contains
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) STOP 4
52 end subroutine
53 end program main