PR c++/86342 - -Wdeprecated-copy and system headers.
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / implicit-firstprivate-ref.f90
blobd00ad27190eb06753c1fe04e62f8e38d0dad9322
1 ! This test checks if the runtime can properly handle implicit
2 ! firstprivate varaibles inside subroutines in modules.
4 ! { dg-do run }
6 module test_mod
7 contains
8 subroutine test(x)
10 IMPLICIT NONE
12 INTEGER :: x, y, j
14 x = 5
16 !$ACC PARALLEL LOOP copyout (y)
17 DO j=1,10
18 y=x
19 ENDDO
20 !$ACC END PARALLEL LOOP
22 y = -1;
24 !$ACC PARALLEL LOOP firstprivate (y) copyout (x)
25 DO j=1,10
26 x=y
27 ENDDO
28 !$ACC END PARALLEL LOOP
29 end subroutine test
30 end module test_mod
32 program t
33 use test_mod
35 INTEGER :: x_min
37 x_min = 8
39 CALL test(x_min)
41 if (x_min .ne. -1) STOP 1
42 end program t