c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / auto_char_len_4.f90
blob16789fafcc70ca914534e458e5612ac9537a31a0
1 ! { dg-do compile }
3 ! Tests the fix for PR25087, in which the following invalid code
4 ! was not detected.
6 ! Contributed by Joost VandeVondele <jv244@cam.ac.uk>
8 ! Modified by Tobias Burnus to fix PR fortran/41235.
10 FUNCTION a()
11 CHARACTER(len=10) :: a
12 a = ''
13 END FUNCTION a
15 SUBROUTINE s(n)
16 CHARACTER(LEN=n), EXTERNAL :: a ! { dg-error "Character length mismatch" }
17 CHARACTER(LEN=n), EXTERNAL :: d ! { dg-error "Character length mismatch" }
18 interface
19 function b (m) ! This is OK
20 CHARACTER(LEN=m) :: b
21 integer :: m
22 end function b
23 end interface
24 write(6,*) a()
25 write(6,*) b(n)
26 write(6,*) c()
27 write(6,*) d()
28 contains
29 function c () ! This is OK
30 CHARACTER(LEN=n):: c
31 c = ""
32 end function c
33 END SUBROUTINE s
35 FUNCTION d()
36 CHARACTER(len=99) :: d
37 d = ''
38 END FUNCTION d