File: declare-variant-11.f90

package info (click to toggle)
gcc-arm-none-eabi 15%3A14.2.rel1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,099,328 kB
  • sloc: cpp: 3,627,108; ansic: 2,571,498; ada: 834,230; f90: 235,082; makefile: 79,231; asm: 74,984; xml: 51,692; exp: 39,736; sh: 33,298; objc: 15,629; python: 15,069; fortran: 14,429; pascal: 7,003; awk: 5,070; perl: 3,106; ml: 285; lisp: 253; lex: 204; haskell: 135
file content (134 lines) | stat: -rw-r--r-- 4,301 bytes parent folder | download
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
! { dg-do compile }
! { dg-additional-options "-foffload=disable -fdump-tree-gimple" }
! { dg-additional-options "-mavx512bw -mavx512vl" { target { i?86-*-* x86_64-*-* } } }

program main
  implicit none
contains
  subroutine f01 ()
  end subroutine

  subroutine f02 ()
  end subroutine

  subroutine f03 ()
    !$omp declare variant (f01) match (device={isa(avx512f,"avx512vl")})
    !$omp declare variant (f02) match (device={isa(avx512bw,avx512vl,"avx512f")})
  end subroutine

  subroutine f04 ()
  end subroutine

  subroutine f05 ()
  end subroutine

  subroutine f06 ()
    !$omp declare variant (f04) match (device={isa(avx512f,avx512vl)})
    !$omp declare variant (f05) match (device={isa(avx512bw,avx512vl,avx512f)})
  end subroutine

  subroutine f07 ()
  end subroutine

  subroutine f08 ()
  end subroutine

  subroutine f09 ()
    !$omp declare variant (f07) match (device={isa(sse4,"sse4.1","sse4.2",sse3,"avx")})
    !$omp declare variant (f08) match (device={isa("avx",sse3)})
  end subroutine

  subroutine f10 ()
  end subroutine

  subroutine f11 ()
  end subroutine

  subroutine f12 ()
  end subroutine

  subroutine f13 ()
    !$omp declare variant (f10) match (device={isa("avx512f")})
    !$omp declare variant (f11) match (user={condition(.true.)},device={isa(avx512f)},implementation={vendor(gnu)})
    !$omp declare variant (f12) match (user={condition(.true. .NEQV. .false.)},device={isa(avx512f)})
  end subroutine

  subroutine f14 ()
  end subroutine

  subroutine f15 ()
  end subroutine

  subroutine f16 ()
  end subroutine

  subroutine f17 ()
  end subroutine

  subroutine f18 ()
    !$omp declare variant (f14) match (construct={teams,do})
    !$omp declare variant (f15) match (construct={teams,parallel,do})
    !$omp declare variant (f16) match (construct={do})
    !$omp declare variant (f17) match (construct={parallel,do})
  end subroutine

  subroutine f19 ()
  end subroutine

  subroutine f20 ()
  end subroutine

  subroutine f21 ()
  end subroutine

  subroutine f22 ()
  end subroutine

  subroutine f23 ()
    !$omp declare variant (f19) match (construct={teams,do})
    !$omp declare variant (f20) match (construct={teams,parallel,do})
    !$omp declare variant (f21) match (construct={do})
    !$omp declare variant (f22) match (construct={parallel,do})
  end subroutine

  subroutine f24 ()
  end subroutine

  subroutine f25 ()
  end subroutine

  subroutine f26 ()
  end subroutine

  subroutine f27 ()
    !$omp declare variant (f24) match (device={kind(cpu)})
    !$omp declare variant (f25) match (device={kind(cpu),isa(avx512f),arch(x86_64)})
    !$omp declare variant (f26) match (device={arch(x86_64),kind(cpu)})
  end subroutine

  subroutine test1
    integer :: i
    call f03 ()	! { dg-final { scan-tree-dump-times "f02 \\\(\\\);" 1 "gimple" { target i?86-*-* x86_64-*-* } } }
		! { dg-final { scan-tree-dump-times "f03 \\\(\\\);" 1 "gimple" { target { ! { i?86-*-* x86_64-*-* } } } } }
    call f09 ()	! { dg-final { scan-tree-dump-times "f07 \\\(\\\);" 1 "gimple" { target i?86-*-* x86_64-*-* } } }
		! { dg-final { scan-tree-dump-times "f09 \\\(\\\);" 1 "gimple" { target { ! { i?86-*-* x86_64-*-* } } } } }
    call f13 ()	! { dg-final { scan-tree-dump-times "f11 \\\(\\\);" 1 "gimple" { target i?86-*-* x86_64-*-* } } }
		! { dg-final { scan-tree-dump-times "f13 \\\(\\\);" 1 "gimple" { target { ! { i?86-*-* x86_64-*-* } } } } }
    !$omp teams distribute parallel do
    do i = 1, 2
      call f18 ()	! { dg-final { scan-tree-dump-times "f15 \\\(\\\);" 1 "gimple" } }
    end do
    !$omp end teams distribute parallel do

    !$omp parallel do
    do i = 1, 2
      call f23 ()	! { dg-final { scan-tree-dump-times "f22 \\\(\\\);" 1 "gimple" } }
    end do
    !$omp end parallel do

    call f27 () ! { dg-final { scan-tree-dump-times "f25 \\\(\\\);" 1 "gimple" { target { { i?86-*-* x86_64-*-* } && { ! ilp32 } } } } }
                ! { dg-final { scan-tree-dump-times "f24 \\\(\\\);" 1 "gimple" { target { { i?86-*-* x86_64-*-* } && { ilp32 } } } } }
		! { dg-final { scan-tree-dump-times "f24 \\\(\\\);" 1 "gimple" { target { ! { nvptx*-*-* amdgcn*-*-* i?86-*-* x86_64-*-* } } } } }
		! { dg-final { scan-tree-dump-times "f27 \\\(\\\);" 1 "gimple" { target { nvptx*-*-* amdgcn*-*-* } } } }
  end subroutine
end program