gcc/libgomp/testsuite/libgomp.fortran/simd5.f90
Jakub Jelinek da6f124d8a langhooks-def.h (LANG_HOOKS_OMP_CLAUSE_LINEAR_CTOR): Define.
* langhooks-def.h (LANG_HOOKS_OMP_CLAUSE_LINEAR_CTOR): Define.
	(LANG_HOOKS_DECLS): Add it.
	* gimplify.c (gimplify_omp_for): Make sure OMP_CLAUSE_LINEAR_STEP
	has correct type.
	* tree.h (OMP_CLAUSE_LINEAR_ARRAY): Define.
	* langhooks.h (struct lang_hooks_for_decls): Add
	omp_clause_linear_ctor hook.
	* omp-low.c (lower_rec_input_clauses): Set max_vf even if
	OMP_CLAUSE_LINEAR_ARRAY is set.  Don't fold_convert
	OMP_CLAUSE_LINEAR_STEP.  For OMP_CLAUSE_LINEAR_ARRAY in
	combined simd loop use omp_clause_linear_ctor hook.
gcc/c/
	* c-typeck.c (c_finish_omp_clauses): Make sure
	OMP_CLAUSE_LINEAR_STEP has correct type.
gcc/cp/
	* semantics.c (finish_omp_clauses): Make sure
	OMP_CLAUSE_LINEAR_STEP has correct type.
gcc/fortran/
	* trans.h (gfc_omp_clause_linear_ctor): New prototype.
	* trans-openmp.c (gfc_omp_linear_clause_add_loop,
	gfc_omp_clause_linear_ctor): New functions.
	(gfc_trans_omp_clauses): Make sure OMP_CLAUSE_LINEAR_STEP has
	correct type.  Set OMP_CLAUSE_LINEAR_ARRAY flag if needed.
	* f95-lang.c (LANG_HOOKS_OMP_CLAUSE_LINEAR_CTOR): Redefine.
libgomp/
	* testsuite/libgomp.fortran/simd5.f90: New test.
	* testsuite/libgomp.fortran/simd6.f90: New test.
	* testsuite/libgomp.fortran/simd7.f90: New test.

From-SVN: r211971
2014-06-25 11:16:12 +02:00

125 lines
2.9 KiB
Fortran

! { dg-do run }
! { dg-additional-options "-msse2" { target sse2_runtime } }
! { dg-additional-options "-mavx" { target avx_runtime } }
integer :: i, j, b, c
c = 0
i = 4
j = 4
b = 7
!$omp simd linear(b:2) reduction(+:c)
do i = 0, 63
c = c + b - (7 + 2 * i)
b = b + 2
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp simd linear(b:3) reduction(+:c)
do i = 0, 63, 4
c = c + b - (7 + i / 4 * 3)
b = b + 3
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 16 * 3) call abort
i = 4
j = 4
b = 7
!$omp simd linear(i) linear(b:2) reduction(+:c)
do i = 0, 63
c = c + b - (7 + 2 * i)
b = b + 2
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp simd linear(i:4) linear(b:3) reduction(+:c)
do i = 0, 63, 4
c = c + b - (7 + i / 4 * 3)
b = b + 3
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 16 * 3) call abort
i = 4
j = 4
b = 7
!$omp simd collapse(2) linear(b:2) reduction(+:c)
do i = 0, 7
do j = 0, 7
c = c + b - (7 + 2 * j + 2 * 8 * i)
b = b + 2
end do
end do
if (c /= 0 .or. i /= 8 .or. j /= 8 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp simd collapse(2) linear(b:2) reduction(+:c) lastprivate (i, j)
do i = 0, 7
do j = 0, 7
c = c + b - (7 + 2 * j + 2 * 8 * i)
b = b + 2
end do
end do
if (c /= 0 .or. i /= 8 .or. j /= 8 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) linear(b:2) reduction(+:c)
do i = 0, 63
c = c + b - (7 + 2 * i)
b = b + 2
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) linear(b:3) reduction(+:c)
do i = 0, 63, 4
c = c + b - (7 + i / 4 * 3)
b = b + 3
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 16 * 3) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) linear(i) linear(b:2) reduction(+:c)
do i = 0, 63
c = c + b - (7 + 2 * i)
b = b + 2
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) linear(i:4) linear(b:3) reduction(+:c)
do i = 0, 63, 4
c = c + b - (7 + i / 4 * 3)
b = b + 3
end do
if (c /= 0 .or. i /= 64 .or. b /= 7 + 16 * 3) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) collapse(2) linear(b:2) reduction(+:c)
do i = 0, 7
do j = 0, 7
c = c + b - (7 + 2 * j + 2 * 8 * i)
b = b + 2
end do
end do
if (c /= 0 .or. i /= 8 .or. j /= 8 .or. b /= 7 + 64 * 2) call abort
i = 4
j = 4
b = 7
!$omp parallel do simd schedule (static, 4) collapse(2) linear(b:2) &
!$omp & reduction(+:c) lastprivate (i, j)
do i = 0, 7
do j = 0, 7
c = c + b - (7 + 2 * j + 2 * 8 * i)
b = b + 2
end do
end do
if (c /= 0 .or. i /= 8 .or. j /= 8 .or. b /= 7 + 64 * 2) call abort
end