1272343Sngie! { dg-do compile }
2272343Sngie! { dg-options "-pedantic -fwhole-file" }
3272343Sngie!
4272343Sngie! Tests the fix for PR25087, in which the following invalid code
5272343Sngie! was not detected.
6272343Sngie!
7272343Sngie! Contributed by Joost VandeVondele  <jv244@cam.ac.uk>
8272343Sngie!
9272343Sngie! Modified by Tobias Burnus to fix PR fortran/41235.
10272343Sngie!
11272343SngieFUNCTION a()
12272343Sngie  CHARACTER(len=10) :: a
13272343Sngie  a = ''
14272343SngieEND FUNCTION a
15272343Sngie
16272343SngieSUBROUTINE s(n)
17272343Sngie  CHARACTER(LEN=n), EXTERNAL :: a  ! { dg-error "Character length mismatch" }
18272343Sngie  CHARACTER(LEN=n), EXTERNAL :: d  ! { dg-error "Character length mismatch" }
19272343Sngie  interface
20272343Sngie    function b (m)                ! This is OK
21272343Sngie      CHARACTER(LEN=m) :: b
22272343Sngie      integer :: m
23272343Sngie    end function b
24272343Sngie  end interface
25272343Sngie  write(6,*) a()
26272343Sngie  write(6,*) b(n)
27272343Sngie  write(6,*) c()
28272343Sngie  write(6,*) d()
29272343Sngiecontains
30272343Sngie    function c ()                ! This is OK
31272343Sngie      CHARACTER(LEN=n):: c
32272343Sngie      c = ""
33272343Sngie    end function c
34272343SngieEND SUBROUTINE s
35272343Sngie
36272343SngieFUNCTION d()
37272343Sngie  CHARACTER(len=99) :: d
38272343Sngie  d = ''
39272343SngieEND FUNCTION d
40272343Sngie