xref: /llvm-project/flang/test/Lower/OpenMP/function-filtering-2.f90 (revision 8f6867c9c6247b394749729757a1ab9acbfa78e6)
1! RUN: %flang_fc1 -fopenmp -fopenmp-version=52 -flang-experimental-hlfir -emit-llvm %s -o - | FileCheck --check-prefixes=LLVM,LLVM-HOST %s
2! RUN: %flang_fc1 -fopenmp -fopenmp-version=52 -emit-hlfir %s -o - | FileCheck --check-prefix=MLIR %s
3! RUN: %if amdgpu-registered-target %{ %flang_fc1 -triple amdgcn-amd-amdhsa -fopenmp -fopenmp-version=52 -fopenmp-is-target-device -flang-experimental-hlfir -emit-llvm %s -o - | FileCheck --check-prefixes=LLVM,LLVM-DEVICE %s %}
4! RUN: %if amdgpu-registered-target %{ %flang_fc1 -triple amdgcn-amd-amdhsa -fopenmp -fopenmp-version=52 -fopenmp-is-target-device -emit-hlfir %s -o - | FileCheck --check-prefix=MLIR %s %}
5! RUN: bbc -fopenmp -fopenmp-version=52 -emit-hlfir %s -o - | FileCheck --check-prefixes=MLIR-HOST,MLIR-ALL %s
6! RUN: %if amdgpu-registered-target %{ bbc -target amdgcn-amd-amdhsa -fopenmp -fopenmp-version=52 -fopenmp-is-target-device -emit-hlfir %s -o - | FileCheck --check-prefixes=MLIR-DEVICE,MLIR-ALL %s %}
7
8! MLIR: func.func @{{.*}}implicit_invocation() attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>}
9! MLIR: return
10! LLVM: define {{.*}} @{{.*}}implicit_invocation{{.*}}(
11subroutine implicit_invocation()
12end subroutine implicit_invocation
13
14! MLIR: func.func @{{.*}}declaretarget() attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>}
15! MLIR: return
16! LLVM: define {{.*}} @{{.*}}declaretarget{{.*}}(
17subroutine declaretarget()
18!$omp declare target to(declaretarget) device_type(nohost)
19    call implicit_invocation()
20end subroutine declaretarget
21
22! MLIR: func.func @{{.*}}declaretarget_enter() attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (enter)>}
23! MLIR: return
24! LLVM: define {{.*}} @{{.*}}declaretarget_enter{{.*}}(
25subroutine declaretarget_enter()
26!$omp declare target enter(declaretarget_enter) device_type(nohost)
27    call implicit_invocation()
28end subroutine declaretarget_enter
29
30! MLIR: func.func @{{.*}}no_declaretarget() attributes {omp.declare_target = #omp.declaretarget<device_type = (nohost), capture_clause = (to)>}
31! MLIR: return
32! LLVM: define {{.*}} @{{.*}}no_declaretarget{{.*}}(
33subroutine no_declaretarget()
34end subroutine no_declaretarget
35
36! MLIR-HOST: func.func @{{.*}}main(
37! MLIR-DEVICE-NOT: func.func @{{.*}}main(
38! MLIR-ALL: return
39
40! LLVM-HOST: define {{.*}} @{{.*}}main{{.*}}(
41! LLVM-HOST: {{.*}} @{{.*}}__omp_offloading{{.*}}main_{{.*}}(
42! LLVM-DEVICE-NOT: {{.*}} @{{.*}}main{{.*}}(
43! LLVM-DEVICE: define {{.*}} @{{.*}}__omp_offloading{{.*}}main_{{.*}}(
44program main
45!$omp target
46    call declaretarget()
47    call no_declaretarget()
48!$omp end target
49end program main
50