Bump version to 19.1.0-rc3
[llvm-project.git] / offload / test / offloading / fortran / target-depend.f90
blob928eb671c970687e58ed462c13360a26faa624ef
1 ! Offloading test checking the use of the depend clause on
2 ! the target construct
3 ! REQUIRES: flang, amdgcn-amd-amdhsa
4 ! UNSUPPORTED: nvptx64-nvidia-cuda
5 ! UNSUPPORTED: nvptx64-nvidia-cuda-LTO
6 ! UNSUPPORTED: aarch64-unknown-linux-gnu
7 ! UNSUPPORTED: aarch64-unknown-linux-gnu-LTO
8 ! UNSUPPORTED: x86_64-pc-linux-gnu
9 ! UNSUPPORTED: x86_64-pc-linux-gnu-LTO
11 ! RUN: %libomptarget-compile-fortran-run-and-check-generic
12 program main
13 implicit none
14 integer :: a = 0
15 INTERFACE
16 FUNCTION omp_get_device_num() BIND(C)
17 USE, INTRINSIC :: iso_c_binding, ONLY: C_INT
18 integer :: omp_get_device_num
19 END FUNCTION omp_get_device_num
20 END INTERFACE
22 call foo(5, a)
23 print*, "======= FORTRAN Test passed! ======="
24 print*, "foo(5) returned ", a, ", expected 6\n"
26 ! stop 0
27 contains
28 subroutine foo(N, r)
29 integer, intent(in) :: N
30 integer, intent(out) :: r
31 integer :: z, i, accumulator
32 z = 1
33 accumulator = 0
34 ! Spawn 3 threads
35 !$omp parallel num_threads(3)
37 ! A single thread will then create two tasks - one is the 'producer' and
38 ! potentially slower task that updates 'z' to 'N'. The second is an
39 ! offloaded target task that increments 'z'. If the depend clauses work
40 ! properly, the target task should wait for the 'producer' task to
41 ! complete before incrementing 'z'. We use 'omp single' here because the
42 ! depend clause establishes dependencies between sibling tasks only.
43 ! This is the easiest way of creating two sibling tasks.
44 !$omp single
45 !$omp task depend(out: z) shared(z)
46 do i=1, 32766
47 ! dumb loop nest to slow down the update of 'z'.
48 ! Adding a function call slows down the producer to the point
49 ! that removing the depend clause from the target construct below
50 ! frequently results in the wrong answer.
51 accumulator = accumulator + omp_get_device_num()
52 end do
53 z = N
54 !$omp end task
56 ! z is 5 now. Increment z to 6.
57 !$omp target map(tofrom: z) depend(in:z)
58 z = z + 1
59 !$omp end target
60 !$omp end single
61 !$omp end parallel
62 ! Use 'accumulator' so it is not optimized away by the compiler.
63 print *, accumulator
64 r = z
65 end subroutine foo
67 !CHECK: ======= FORTRAN Test passed! =======
68 !CHECK: foo(5) returned 6 , expected 6
69 end program main