]> git.ipfire.org Git - thirdparty/gcc.git/blob - gcc/testsuite/gfortran.dg/goacc/pure-elemental-procedures.f95
Merge current set of OpenACC changes from gomp-4_0-branch.
[thirdparty/gcc.git] / gcc / testsuite / gfortran.dg / goacc / pure-elemental-procedures.f95
1 ! { dg-do compile }
2 ! { dg-additional-options "-std=f2008 -fcoarray=single" }
3
4 module test
5 implicit none
6 contains
7 elemental subroutine test1
8 !$acc parallel ! { dg-error "may not appear in PURE procedures" }
9 end subroutine test1
10
11 pure subroutine test2
12 !$acc parallel ! { dg-error "may not appear in PURE procedures" }
13 end subroutine test2
14
15 ! Implicit pure
16 elemental real function test3(x)
17 real, intent(in) :: x
18 !$acc parallel ! { dg-error "may not appear in PURE procedures" }
19 test3 = x*x
20 end function test3
21
22 pure real function test4(x)
23 real, intent(in) :: x
24 !$acc parallel ! { dg-error "may not appear in PURE procedures" }
25 test4 = x
26 end function test4
27
28 subroutine test5
29 real :: x = 0.0
30 integer :: i
31 !$acc parallel loop collapse(1) reduction(+:x)
32 do i = 1,10
33 x = x + 0.3
34 enddo
35 print *, x
36 end subroutine test5
37
38 real function test6(x)
39 real :: x
40 integer :: i
41 !$acc parallel loop collapse(1) reduction(+:x)
42 do i = 1,10
43 x = x + 0.3
44 enddo
45 test6 = x
46 end function test6
47
48 impure elemental real function test7(x)
49 real, intent(in) :: x
50 !$acc parallel
51 test7 = x
52 !$acc end parallel
53 end function test7
54
55 subroutine test8
56 real :: x = 0.0
57 integer :: i
58 !$acc parallel loop collapse(1) reduction(+:x)
59 do i = 1,10
60 critical ! { dg-error "CRITICAL block inside of" }
61 x = x + 0.3
62 end critical
63 enddo
64 print *, x
65 end subroutine test8
66
67 real function test9(n)
68 integer, value :: n
69 BLOCK
70 integer i
71 real sum
72 !$acc loop reduction(+:sum)
73 do i=1, n
74 sum = sum + sin(real(i))
75 end do
76 END BLOCK
77 end function test9
78 end module test