[clangd] Re-land "support outgoing calls in call hierarchy" (#117673)
[llvm-project.git] / flang / test / Semantics / OpenMP / declare-target07.f90
blob22b4a4bd081d755980cfa0e19e7f15f0533d97b9
1 ! RUN: %python %S/../test_errors.py %s %flang_fc1 -fopenmp
3 module my_module
4 interface foo
5 subroutine foo_int(a)
6 integer :: a
7 end subroutine
8 subroutine foo_real(a)
9 real :: a
10 end subroutine
11 end interface
12 contains
13 subroutine bar(N)
14 integer :: N
15 entry entry1(N)
16 end subroutine
17 subroutine foobar(N)
18 integer::N
19 !ERROR: The procedure 'entry1' in DECLARE TARGET construct cannot be an entry name.
20 !$omp declare target(bar, entry1)
21 call bar(N)
22 end subroutine
23 end module
25 module other_mod
26 abstract interface
27 integer function foo(a)
28 integer, intent(in) :: a
29 end function
30 end interface
31 procedure(foo), pointer :: procptr
32 !ERROR: The procedure 'procptr' in DECLARE TARGET construct cannot be a procedure pointer.
33 !$omp declare target(procptr)
34 end module
36 subroutine baz(x)
37 real, intent(inout) :: x
38 real :: res
39 stmtfunc(x) = 4.0 * (x**3)
40 !ERROR: The procedure 'stmtfunc' in DECLARE TARGET construct cannot be a statement function.
41 !$omp declare target (stmtfunc)
42 res = stmtfunc(x)
43 end subroutine
45 program main
46 use my_module
47 !ERROR: The procedure 'foo' in DECLARE TARGET construct cannot be a generic name.
48 !$omp declare target(foo)
49 end