xref: /llvm-project/flang/test/Integration/OpenMP/target-filtering.f90 (revision 8f6867c9c6247b394749729757a1ab9acbfa78e6)
1!===----------------------------------------------------------------------===!
2! This directory can be used to add Integration tests involving multiple
3! stages of the compiler (for eg. from Fortran to LLVM IR). It should not
4! contain executable tests. We should only add tests here sparingly and only
5! if there is no other way to test. Repeat this message in each test that is
6! added to this directory and sub-directories.
7!===----------------------------------------------------------------------===!
8
9!RUN: %flang_fc1 -emit-llvm -fopenmp %s -o - | FileCheck %s --check-prefixes HOST,ALL
10!RUN: %if amdgpu-registered-target %{ %flang_fc1 -triple amdgcn-amd-amdhsa -emit-llvm -fopenmp -fopenmp-is-target-device %s -o - | FileCheck %s --check-prefixes DEVICE,ALL %}
11
12!HOST: define {{.*}}@{{.*}}before{{.*}}(
13!DEVICE-NOT: define {{.*}}@before{{.*}}(
14!DEVICE-NOT: declare {{.*}}@before{{.*}}
15integer function before(x)
16   integer, intent(in) :: x
17   before = x + 200
18end function
19
20!ALL: define {{.*}}@{{.*}}main{{.*}}(
21program main
22   integer :: x, before, after
23   !$omp target map(tofrom : x)
24      x = 100
25   !$omp end target
26   !HOST: call {{.*}}@{{.*}}before{{.*}}(
27   !DEVICE-NOT: call {{.*}}@before{{.*}}(
28   !HOST: call {{.*}}@{{.*}}after{{.*}}(
29   !DEVICE-NOT: call {{.*}}@after{{.*}}(
30   x = x + before(x) + after(x)
31end program
32
33!HOST: define {{.*}}@{{.*}}after{{.*}}(
34!DEVICE-NOT: define {{.*}}@after{{.*}}(
35!DEVICE-NOT: declare {{.*}}@after{{.*}}
36integer function after(x)
37   integer, intent(in) :: x
38   after = x + 300
39end function
40
41!ALL: define {{.*}}@{{.*}}before_target{{.*}}(
42subroutine before_target(x)
43   integer, intent(out) :: x
44   !$omp target map(from: x)
45      x = 1
46   !$omp end target
47end subroutine
48
49!ALL: define {{.*}}@{{.*}}middle{{.*}}(
50subroutine middle()
51   integer :: x
52   !$omp target map(from: x)
53      x = 0
54   !$omp end target
55   !HOST: call {{.*}}@{{.*}}before_target{{.*}}(
56   !DEVICE-NOT: call {{.*}}@{{.*}}before_target{{.*}}(
57   !HOST: call {{.*}}@{{.*}}after_target{{.*}}(
58   !DEVICE-NOT: call {{.*}}@{{.*}}after_target{{.*}}(
59   call before_target(x)
60   call after_target(x)
61end subroutine
62
63!ALL: define {{.*}}@{{.*}}after_target{{.*}}(
64subroutine after_target(x)
65   integer, intent(out) :: x
66   !$omp target map(from:x)
67      x = 2
68   !$omp end target
69end subroutine
70