aarch64: Add vector floating point extend pattern [PR113880, PR113869]
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocate_zerosize_2.f90
blobbd6d299f4b6f059dc6dc73a251a01ba14f19bf55
1 ! { dg-do run }
2 ! PR 27980 - We used to allocate negative amounts of memory
3 ! for functions returning arrays if lbound > ubound-1.
4 ! Based on a test case by beliavsky@aol.com posted to
5 ! comp.lang.fortran.
6 program xint_func
7 implicit none
8 integer, parameter :: n=3,ii(n)=(/2,0,-1/)
9 integer :: i
10 character(len=80) :: line
11 do i=1,n
12 write (line,'(10I5)') int_func(ii(i))
13 end do
14 contains
15 function int_func(n) result(ivec)
16 integer, intent(in) :: n
17 integer :: ivec(n)
18 integer :: i
19 if (n > 0) then
20 forall (i=1:n) ivec(i) = i
21 end if
22 end function int_func
23 end program xint_func