aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/examples-4/simd-6.f90
blob: 7540a945628408293dd4f965a0492954fd1cef06 (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
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
! { dg-do run { target vect_simd_clones } }
! { dg-additional-options "-msse2" { target sse2_runtime } }
! { dg-additional-options "-mavx" { target avx_runtime } }

module SIMD6_mod
contains
  function foo(p) result(r)
  !$omp declare simd(foo) notinbranch
    integer :: p, r
    p = p + 10
    r = p
  end function foo

  function myaddint(a, b, n) result(r)
    implicit none
    integer :: a(*), b(*), n, r
    integer :: i

    !$omp simd
    do i=1, n
        a(i) = foo(b(i))  ! foo is not called under a condition
    end do
    r = a(n)

  end function myaddint

  function myaddint_ref(a, b, n) result(r)
    implicit none
    integer :: a(*), b(*), n, r
    integer :: i

    do i=1, n
        a(i) = foo(b(i))
    end do
    r = a(n)

  end function myaddint_ref

  function goo(p) result(r)
  !$omp declare simd(goo) inbranch
    real :: p, r
    p = p + 18.5
    r = p
  end function goo

  function myaddfloat(x, y, n) result(r)
    implicit none
    real :: x(*), y(*), r
    integer :: n
    integer :: i

    !$omp simd
    do i=1, n
       if (x(i) > y(i)) then
          x(i) = goo(y(i))
          ! goo is called under the condition (or within a branch)
       else
          x(i) = y(i)
       endif
    end do

    r = x(n)
  end function myaddfloat

  function myaddfloat_ref(x, y, n) result(r)
    implicit none
    real :: x(*), y(*), r
    integer :: n
    integer :: i

    do i=1, n
       if (x(i) > y(i)) then
          x(i) = goo(y(i))
       else
          x(i) = y(i)
       endif
    end do

    r = x(n)
  end function myaddfloat_ref

  subroutine init (b, y, n)
    integer :: b(128)
    real :: y(128)

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

  end subroutine

  subroutine init2 (b, y, n)
    integer :: b(128)
    real :: y(128)

    do i = 1, n
      b(i) = i
      y(i) = i
    end do

  end subroutine

  subroutine checkfloat (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

  subroutine checkint (a, b, n)
      integer :: i, n, a(*), b(*)
      do i = 1, n
        if (a(i) .ne. b(i)) stop 2
      end do
  end subroutine

  subroutine test ()
    integer :: a(128), a_ref(128), b(128), ri, ri_ref
    real :: x(128), x_ref(128), y(128), rf, rf_ref

    call  init2(a, x, 128)
    call  init2(a_ref, x_ref, 128)

    call  init(b, y, 128)

    ri = myaddint (a, b, 128)
    rf = myaddfloat (x, y, 128)

    call init(b, y, 128)

    ri_ref = myaddint_ref (a_ref, b, 128)
    rf_ref = myaddfloat_ref (x_ref, y, 128)

    call checkint (a, a_ref, 128)
    call checkfloat (x, x_ref, 128)
  end subroutine

end module

program SIMD6
  use SIMD6_mod, only: test

  call test ()

end program