1! { dg-do compile }
2! { dg-require-effective-target vect_float }
3! { dg-additional-options "--param vect-max-peeling-for-alignment=0" }
4
5SUBROUTINE FOO(A, B, C)
6DIMENSION A(1000000), B(1000000), C(1000000)
7READ*, X, Y
8A = LOG(X); B = LOG(Y); C = A + B
9PRINT*, C(500000)
10END
11
12! First loop (A=LOG(X)) is vectorized using peeling to align the store.
13! Same for the second loop (B=LOG(Y)).
14! Third loop (C = A + B) is vectorized using versioning (for targets that don't
15! support unaligned loads) or using peeling to align the store (on targets that
16! support unaligned loads).
17
18! { dg-final { scan-tree-dump-times "vectorized 3 loops" 1 "vect" } }
19! { dg-final { scan-tree-dump-times "Alignment of access forced using versioning." 3 "vect" { target { { vect_no_align && { ! vect_hw_misalign } } || { { ! vector_alignment_reachable  } && { ! vect_hw_misalign } } } } } }
20