PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocatable_scalar_12.f90
blob3521468e4918a069dbb12009ac2d24d9b3eab9e3
1 ! { dg-do run }
3 ! PR fortran/47421
5 ! Don't auto-deallocatable scalar character allocatables.
7 implicit none
8 character(len=5), allocatable :: str
9 allocate(str)
10 str = '1bcde'
11 if(str /= '1bcde') STOP 1
12 call sub(str,len(str))
13 if(str /= '1bcde') STOP 2
14 call subOUT(str,len(str))
15 if (len(str) /= 5) STOP 3
16 if(allocated(str)) STOP 4
17 contains
18 subroutine sub(x,n)
19 integer :: n
20 character(len=n), allocatable :: x
21 if(len(x) /= 5) STOP 5
22 if(x /= '1bcde') STOP 6
23 end subroutine sub
24 subroutine subOUT(x,n)
25 integer :: n
26 character(len=n), allocatable,intent(out) :: x
27 if(allocated(x)) STOP 7
28 if(len(x) /= 5) STOP 8
29 end subroutine subOUT
30 end