Add support for ARMv8-R architecture
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / examples-4 / simd-6.f90
blob5cb1e047cbd8f9b34267d649bf53ec6e2c9c0802
1 ! { dg-do run { target vect_simd_clones } }
2 ! { dg-additional-options "-msse2" { target sse2_runtime } }
3 ! { dg-additional-options "-mavx" { target avx_runtime } }
5 module SIMD6_mod
6 contains
7 function foo(p) result(r)
8 !$omp declare simd(foo) notinbranch
9 integer :: p, r
10 p = p + 10
11 r = p
12 end function foo
14 function myaddint(a, b, n) result(r)
15 implicit none
16 integer :: a(*), b(*), n, r
17 integer :: i
19 !$omp simd
20 do i=1, n
21 a(i) = foo(b(i)) ! foo is not called under a condition
22 end do
23 r = a(n)
25 end function myaddint
27 function myaddint_ref(a, b, n) result(r)
28 implicit none
29 integer :: a(*), b(*), n, r
30 integer :: i
32 do i=1, n
33 a(i) = foo(b(i))
34 end do
35 r = a(n)
37 end function myaddint_ref
39 function goo(p) result(r)
40 !$omp declare simd(goo) inbranch
41 real :: p, r
42 p = p + 18.5
43 r = p
44 end function goo
46 function myaddfloat(x, y, n) result(r)
47 implicit none
48 real :: x(*), y(*), r
49 integer :: n
50 integer :: i
52 !$omp simd
53 do i=1, n
54 if (x(i) > y(i)) then
55 x(i) = goo(y(i))
56 ! goo is called under the condition (or within a branch)
57 else
58 x(i) = y(i)
59 endif
60 end do
62 r = x(n)
63 end function myaddfloat
65 function myaddfloat_ref(x, y, n) result(r)
66 implicit none
67 real :: x(*), y(*), r
68 integer :: n
69 integer :: i
71 do i=1, n
72 if (x(i) > y(i)) then
73 x(i) = goo(y(i))
74 else
75 x(i) = y(i)
76 endif
77 end do
79 r = x(n)
80 end function myaddfloat_ref
82 subroutine init (b, y, n)
83 integer :: b(128)
84 real :: y(128)
86 s = -1
87 do i = 1, n
88 b(i) = i*i*s
89 y(i) = i*i*s
90 s = -s
91 end do
93 end subroutine
95 subroutine init2 (b, y, n)
96 integer :: b(128)
97 real :: y(128)
99 do i = 1, n
100 b(i) = i
101 y(i) = i
102 end do
104 end subroutine
106 subroutine checkfloat (a, b, n)
107 integer :: i, n
108 real, parameter :: EPS = 0.000001
109 real :: diff, a(*), b(*)
110 do i = 1, n
111 diff = a(i) - b(i)
112 if (diff > EPS .or. -diff > EPS) call abort
113 end do
114 end subroutine
116 subroutine checkint (a, b, n)
117 integer :: i, n, a(*), b(*)
118 do i = 1, n
119 if (a(i) .ne. b(i)) call abort
120 end do
121 end subroutine
123 subroutine test ()
124 integer :: a(128), a_ref(128), b(128), ri, ri_ref
125 real :: x(128), x_ref(128), y(128), rf, rf_ref
127 call init2(a, x, 128)
128 call init2(a_ref, x_ref, 128)
130 call init(b, y, 128)
132 ri = myaddint (a, b, 128)
133 rf = myaddfloat (x, y, 128)
135 call init(b, y, 128)
137 ri_ref = myaddint_ref (a_ref, b, 128)
138 rf_ref = myaddfloat_ref (x_ref, y, 128)
140 call checkint (a, a_ref, 128)
141 call checkfloat (x, x_ref, 128)
142 end subroutine
144 end module
146 program SIMD6
147 use SIMD6_mod, only: test
149 call test ()
151 end program