aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/examples-4/simd-4.f90
blob: 551b8396f13d4bac3edce82cf06281a0332e70af (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
! { dg-do run }
! { dg-additional-options "-msse2" { target sse2_runtime } }
! { dg-additional-options "-mavx" { target avx_runtime } }

module SIMD4_mod
contains
  subroutine work( b, n, m )
     implicit none
     real       :: b(n)
     integer    :: i,n,m

     call init(b, n)

     !$omp simd safelen(16)
     do i = m+1, n
        b(i) = b(i-m) - 1.0
     end do
  end subroutine work

  subroutine work_ref( b, n, m )
     implicit none
     real       :: b(n)
     integer    :: i,n,m

     call init(b, n)

     do i = m+1, n
        b(i) = b(i-m) - 1.0
     end do
  end subroutine work_ref

  subroutine init (b, n)
    real             :: b(*)
    integer          :: n, i, s

    s = -1
    do i = 1, n
      b(i) = i * i * s
      s = -s
    end do

  end subroutine

  subroutine check (a, b, n)
    integer :: i, n
    real, parameter :: EPS = 0.000001
    real :: 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 SIMD4
  use SIMD4_mod
  real :: b(128), b_ref(128)

  call  work(b, 128, 32)
  call  work_ref(b_ref, 128, 32)

  call check(b, b_ref, 128)
end program