File: declare-target-implicit-tarop-cap.f90

package info (click to toggle)
llvm-toolchain-19 1%3A19.1.7-3
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 1,998,520 kB
  • sloc: cpp: 6,951,680; ansic: 1,486,157; asm: 913,598; python: 232,024; f90: 80,126; objc: 75,281; lisp: 37,276; pascal: 16,990; sh: 10,009; ml: 5,058; perl: 4,724; awk: 3,523; makefile: 3,167; javascript: 2,504; xml: 892; fortran: 664; cs: 573
file content (85 lines) | stat: -rw-r--r-- 3,417 bytes parent folder | download | duplicates (5)
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
!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s
!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-is-device %s -o - | FileCheck %s  --check-prefix=DEVICE
!RUN: bbc -emit-hlfir -fopenmp %s -o - | FileCheck %s
!RUN: bbc -emit-hlfir -fopenmp -fopenmp-is-target-device %s -o - | FileCheck %s --check-prefix=DEVICE

! DEVICE-LABEL: func.func @_QPimplicit_capture
! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
function implicit_capture() result(i)
   implicit none
   integer :: i
   i = 1
end function implicit_capture

subroutine subr_target()
   integer :: n
!$omp target map(tofrom:n)
   n = implicit_capture()
!$omp end target
end subroutine

!! -----

! CHECK-LABEL: func.func @_QPimplicitly_captured_nest_twice
! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}}
function implicitly_captured_nest_twice() result(i)
   integer :: i
   i = 10
end function implicitly_captured_nest_twice

! CHECK-LABEL: func.func @_QPimplicitly_captured_one_twice
! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}}
function implicitly_captured_one_twice() result(k)
!$omp declare target to(implicitly_captured_one_twice) device_type(host)
   k = implicitly_captured_nest_twice()
end function implicitly_captured_one_twice

! CHECK-LABEL: func.func @_QPimplicitly_captured_nest_twice_enter
! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
function implicitly_captured_nest_twice_enter() result(i)
   integer :: i
   i = 10
end function implicitly_captured_nest_twice_enter

! CHECK-LABEL: func.func @_QPimplicitly_captured_one_twice_enter
! CHECK-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (host), capture_clause = (enter)>{{.*}}}
function implicitly_captured_one_twice_enter() result(k)
!$omp declare target enter(implicitly_captured_one_twice_enter) device_type(host)
   k = implicitly_captured_nest_twice_enter()
end function implicitly_captured_one_twice_enter

! DEVICE-LABEL: func.func @_QPimplicitly_captured_two_twice
! DEVICE-SAME: {{.*}}attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
function implicitly_captured_two_twice() result(y)
   integer :: y
   y = 5
end function implicitly_captured_two_twice


function target_function_test_device() result(j)
   integer :: i, j
   !$omp target map(tofrom: i, j)
   i = implicitly_captured_one_twice()
   j = implicitly_captured_two_twice() + i
   !$omp end target
end function target_function_test_device

!! -----

! DEVICE-LABEL: func.func @_QPimplicitly_captured_recursive
! DEVICE-SAME: {{.*}}attributes {fir.func_recursive, omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>{{.*}}}
recursive function implicitly_captured_recursive(increment) result(k)
   integer :: increment, k
   if (increment == 10) then
      k = increment
   else
      k = implicitly_captured_recursive(increment + 1)
   end if
end function implicitly_captured_recursive

function target_function_recurse() result(i)
   integer :: i
   !$omp target map(tofrom: i)
   i = implicitly_captured_recursive(0)
   !$omp end target
end function target_function_recurse