xref: /llvm-project/flang/test/Lower/OpenMP/declare-target-unnamed-main.f90 (revision 03579455bd941da6278f883ed8827ef0fbeb5e50)
1!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s
2!RUN: %flang_fc1 -emit-hlfir -fopenmp -fopenmp-is-device %s -o - | FileCheck %s
3
4! This test is a reduced version of the example in issue 63362.
5! It aims to test that no crash occurs when declare target is
6! utilised within an unnamed main program and that we still
7! appropriately mark the function as declare target, even when
8! unused within the target region.
9
10!CHECK: func.func @_QPfoo(%{{.*}}: !fir.ref<f32>{{.*}}) -> f32 attributes {{{.*}}omp.declare_target = #omp.declaretarget<device_type = (any), capture_clause = (to)>{{.*}}}
11
12interface
13real function foo (x)
14  !$omp declare target
15  real, intent(in) :: x
16end function foo
17end interface
18integer, parameter :: n = 1000
19integer, parameter :: c = 100
20integer :: i, j
21real :: a(n)
22do i = 1, n
23a(i) = i
24end do
25do i = 1, n, c
26  !$omp target map(a(i:i+c-1))
27    !$omp parallel do
28      do j = i, i + c - 1
29        a(j) = a(j)
30      end do
31  !$omp end target
32end do
33do i = 1, n
34if (a(i) /= i + 1) stop 1
35end do
36end
37real function foo (x)
38!$omp declare target
39real, intent(in) :: x
40foo = x + 1
41end function foo
42