[to-be-committed] [RISC-V] Use Zbkb for general 64 bit constants when profitable
[official-gcc.git] / gcc / testsuite / gfortran.dg / array_memset_2.f90
blob06f33653d7d26cf4a2c1a164eacf05a5d6932fa7
1 ! { dg-do run }
2 ! { dg-options "-O2 -fdump-tree-original" }
4 module foo
5 contains
6 subroutine bar(a)
7 real, dimension(:,:) :: a
8 a(1,:) = 0.
9 end subroutine bar
10 end module foo
12 program test
13 use foo
14 implicit none
15 real, dimension (2,2) :: a, d, e
16 real, dimension (1,2) :: b
17 real, dimension (2) :: c
18 data a, d, e /12*1.0/
19 data b /2*1.0/
20 data c /2*1.0/
22 a(1,:) = 0. ! This can't be optimized to a memset.
23 b(1,:) = 0. ! This is optimized to = {}.
24 c = 0. ! This is optimized to = {}.
25 d(:,1) = 0. ! This can't be otimized to a memset.
26 call bar(e)
28 if (any(a /= reshape((/ 0.0, 1.0, 0.0, 1.0/), shape(a)))) STOP 1
29 if (any(b /= 0.)) STOP 2
30 if (any(c /= 0.)) STOP 3
31 if (any(d /= reshape((/ 0.0, 0.0, 1.0, 1.0/), shape(d)))) STOP 4
32 if (any(e /= reshape((/ 0.0, 1.0, 0.0, 1.0/), shape(e)))) STOP 5
34 end program
36 ! { dg-final { scan-tree-dump-times "= {}" 2 "original" } }