xref: /llvm-project/flang/test/Lower/OpenMP/function-filtering-3.f90 (revision 8f6867c9c6247b394749729757a1ab9acbfa78e6)
1! RUN: %flang_fc1 -fopenmp -flang-experimental-hlfir -emit-llvm %s -o - | FileCheck --check-prefixes=LLVM-HOST,LLVM-ALL %s
2! RUN: %flang_fc1 -fopenmp -emit-hlfir %s -o - | FileCheck --check-prefixes=MLIR-HOST,MLIR-ALL %s
3! RUN: %if amdgpu-registered-target %{ %flang_fc1 -triple amdgcn-amd-amdhsa -fopenmp -fopenmp-is-target-device -flang-experimental-hlfir -emit-llvm %s -o - | FileCheck --check-prefixes=LLVM-DEVICE,LLVM-ALL %s %}
4! RUN: %if amdgpu-registered-target %{ %flang_fc1 -triple amdgcn-amd-amdhsa -fopenmp -fopenmp-is-target-device -emit-hlfir %s -o - | FileCheck --check-prefixes=MLIR-DEVICE,MLIR-ALL %s %}
5! RUN: bbc -fopenmp -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-is-target-device -emit-hlfir %s -o - | FileCheck --check-prefixes=MLIR-DEVICE,MLIR-ALL %s %}
7
8! Check that the correct LLVM IR functions are kept for the host and device
9! after running the whole set of translation and transformation passes from
10! Fortran.
11
12! MLIR-HOST: func.func @{{.*}}host_parent_procedure(
13! MLIR-HOST: return
14! MLIR-DEVICE-NOT: func.func {{.*}}host_parent_procedure(
15
16! LLVM-HOST: define {{.*}} @host_parent_procedure{{.*}}(
17! LLVM-DEVICE-NOT: {{.*}} @{{.*}}_host_parent_procedure{{.*}}(
18subroutine host_parent_procedure(x)
19  integer, intent(out) :: x
20  call target_internal_proc(x)
21contains
22! MLIR-ALL: func.func {{.*}}@_QFhost_parent_procedurePtarget_internal_proc(
23
24! LLVM-HOST: define {{.*}} @_QFhost_parent_procedurePtarget_internal_proc(
25! LLVM-DEVICE-NOT: define {{.*}} @_QFhost_parent_procedurePtarget_internal_proc(
26! LLVM-ALL: define {{.*}} @__omp_offloading_{{.*}}QFhost_parent_procedurePtarget_internal_proc{{.*}}(
27
28subroutine target_internal_proc(x)
29  integer, intent(out) :: x
30  !$omp target map(from:x)
31    x = 10
32  !$omp end target
33end subroutine
34end subroutine
35