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

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (69 lines) | stat: -rw-r--r-- 2,482 bytes parent folder | download | duplicates (3)
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
!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
!RUN: %flang_fc1 -emit-fir -fopenmp -fopenmp-is-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

! 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 {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