arm: Add .type and .size to __gnu_cmse_nonsecure_call [PR115360]
[official-gcc.git] / gcc / testsuite / gfortran.dg / deferred_character_18.f90
blob1b1457fa293c03310e8773c1decf9ffec8456d31
1 ! { dg-do compile }
2 ! PR Fortran/82367
3 ! Contributed by Walter Spector <w6ws at earthlink dot net>
4 module cls_allocmod
5 implicit none
7 contains
9 subroutine cls_alloc (n, str)
10 integer, intent(in) :: n
11 character(*), allocatable, intent(out) :: str
12 ! Note: Star ^ should have been a colon (:)
14 allocate (character(n)::str)
16 end subroutine
18 end module
20 program cls
21 use cls_allocmod
22 implicit none
24 character(:), allocatable :: s
26 call cls_alloc(42, s) ! { dg-error "allocatable or pointer dummy argument" }
27 print *, 'string len =', len(s)
29 end program