PR target/83368
[official-gcc.git] / gcc / testsuite / gfortran.dg / save_6.f90
blob0dcec29d5f72867e7c00c116b4c071c3d40ff623
1 ! { dg-do run }
2 ! { dg-require-effective-target lto }
3 ! { dg-options "-fno-automatic -flto -g" }
5 ! PR fortran/55733
7 ! Check that -fno-automatic makes the local variable SAVEd
8 ! Check that -flto -g works
11 ! Scalar allocatable
12 subroutine foo(i)
13 integer :: i
14 integer, allocatable :: j
15 if (i == 1) j = 42
16 if (.not. allocated (j)) call abort ()
17 if (j /= 42) call abort ()
18 end
20 ! Deferred-length string scalar
21 subroutine bar()
22 logical, save :: first = .true.
23 character(len=:), allocatable :: str
24 if (first) then
25 first = .false.
26 if (allocated (str)) call abort ()
27 str = "ABCDEF"
28 end if
29 if (.not. allocated (str)) call abort ()
30 if (len (str) /= 6) call abort ()
31 if (str(1:6) /= "ABCDEF") call abort ()
32 end subroutine bar
34 ! Deferred-length string array
35 subroutine bar_array()
36 logical, save :: first = .true.
37 character(len=:), allocatable :: str
38 if (first) then
39 first = .false.
40 if (allocated (str)) call abort ()
41 str = "ABCDEF"
42 end if
43 if (.not. allocated (str)) call abort ()
44 if (len (str) /= 6) call abort ()
45 if (str(1:6) /= "ABCDEF") call abort ()
46 end subroutine bar_array
48 call foo(1)
49 call foo(2)
50 call bar()
51 call bar_array()
52 call bar()
53 call bar_array()
54 end