aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / optional_assumed_charlen_2.f90
blobfa8cfd7903824f96db87e95127f85e5fa01ea13d
1 ! { dg-do run }
2 ! PR fortran/94672
4 ! Contributed by Tomáš Trnka
6 module m
7 implicit none (type,external)
8 type t
9 integer :: i = 5
10 end type t
11 contains
12 subroutine bar(x, y, z, n)
13 integer, value :: n
14 type(t), intent(out), optional :: x(:), y(n), z(:)
15 allocatable :: z
16 end subroutine bar
18 subroutine foo (n, nFound, sVal)
19 integer, value :: n
20 integer, intent(out) :: nFound
21 character(*), optional, intent(out) :: sVal(n)
23 nFound = 0
25 if (present(sVal)) then
26 nFound = nFound + 1
27 end if
28 end subroutine
29 end
31 use m
32 implicit none (type,external)
33 type(t) :: a(7), b(7), c(:)
34 allocatable :: c
35 integer :: nn, nf
36 character(len=4) :: str
38 allocate(c(7))
39 call bar(a,b,c,7)
40 if (any(a(:)%i /= 5)) stop 1
41 if (any(b(:)%i /= 5)) stop 2
42 if (allocated(c)) stop 3
44 call foo(7, nf, str)
45 if (nf /= 1) stop 4
46 call foo(7, nf)
47 if (nf /= 0) stop 5
48 end