aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/examples-4/simd-2.f90
blob: 3bb88388ad2e97c61314348c2f8f9900b99d4c00 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
! { dg-do run { target vect_simd_clones } }
! { dg-additional-options "-msse2" { target sse2_runtime } }
! { dg-additional-options "-mavx" { target avx_runtime } }

module SIMD2_mod
contains
  function add1(a,b,fact) result(c)
  !$omp declare simd(add1) uniform(fact)
     double precision :: a,b,fact, c
     c = a + b + fact
  end function

  function add2(a,b,i, fact) result(c)
  !$omp declare simd(add2) uniform(a,b,fact) linear(i:1)
     integer,          value        :: i
     double precision, dimension(:) :: a, b
     double precision               :: fact, c
     c = a(i) + b(i) + fact
  end function

  subroutine work(a, b, n )
     implicit none
     double precision           :: a(n),b(n), tmp
     integer                    :: n, i

     !$omp simd private(tmp)
     do i = 1,n
        tmp  = add1(a(i), b(i), 1.0d0)
        a(i) = add2(a,    b, i, 1.0d0) + tmp
        a(i) = a(i) + b(i) + 1.0d0
     end do
  end subroutine

  subroutine work_ref(a, b, n )
     implicit none
     double precision           :: a(n),b(n), tmp
     integer                    :: n, i

     do i = 1,n
        tmp  = add1(a(i), b(i), 1.0d0)
        a(i) = add2(a,    b, i, 1.0d0) + tmp
        a(i) = a(i) + b(i) + 1.0d0
     end do
  end subroutine

  subroutine check (a, b, n)
      integer :: i, n
      double precision, parameter :: EPS = 0.0000000000001
      double precision :: diff, a(*), b(*)
      do i = 1, n
        diff = a(i) - b(i)
        if (diff > EPS .or. -diff > EPS) stop 1
      end do
  end subroutine
end module

program main
   use SIMD2_mod
   integer, parameter :: N=32
   integer :: i
   double precision   :: a(N), b(N), a_ref(N)
   do i = 1,N
      a(i) = i-1
      a_ref(i) = a(i)
      b(i) = N-(i-1)
   end do

   call work(a, b, N )
   call work_ref(a_ref, b, N )

   call check(a, a_ref, N )
end program