[AArch64] Merge stores of D-register values with different modes
[official-gcc.git] / gcc / testsuite / gfortran.dg / array_function_2.f90
bloba9374116a418ea29b0e5087995bb4ad1229676e1
1 ! { dg-do run }
2 ! { dg-options "-fbounds-check" }
4 ! PR fortran/37199
5 ! We used to produce wrong (segfaulting) code for this one because the
6 ! temporary array for the function result had wrong bounds.
8 ! Contributed by Gavin Salam <salam@lpthe.jussieu.fr>
10 program bounds_issue
11 implicit none
12 integer, parameter :: dp = kind(1.0d0)
13 real(dp), pointer :: pdf0(:,:), dpdf(:,:)
15 allocate(pdf0(0:282,-6:7))
16 allocate(dpdf(0:282,-6:7)) ! with dpdf(0:283,-6:7) [illegal] error disappears
17 !write(0,*) lbound(dpdf), ubound(dpdf)
18 dpdf = tmp_PConv(pdf0)
20 contains
21 function tmp_PConv(q_in) result(Pxq)
22 real(dp), intent(in) :: q_in(0:,-6:)
23 real(dp) :: Pxq(0:ubound(q_in,dim=1),-6:7)
24 Pxq = 0d0
25 !write(0,*) lbound(q_in), ubound(q_in)
26 !write(0,*) lbound(Pxq), ubound(Pxq)
27 return
28 end function tmp_PConv
30 end program bounds_issue