c-family: Enable -fpermissive for C and ObjC
[official-gcc.git] / libgomp / testsuite / libgomp.oacc-fortran / pr96628-part1.f90
blob06512d43c0589d05c39b2fbbca403a6c04610bae
1 ! { dg-do run }
2 ! { dg-additional-sources pr96628-part2.f90 }
3 ! { dg-additional-options "-ftree-slp-vectorize" }
5 ! This file is compiled first
7 ! { dg-additional-options -Wuninitialized }
9 module m2
10 real*8 :: mysum
11 !$acc declare device_resident(mysum)
12 contains
13 SUBROUTINE one(t)
14 !$acc routine
15 REAL*8, INTENT(IN) :: t(:)
16 mysum = sum(t)
17 END SUBROUTINE one
18 SUBROUTINE two(t)
19 !$acc routine seq
20 REAL*8, INTENT(INOUT) :: t(:)
21 t = (100.0_8*t)/sum
22 ! { dg-warning {'sum' is used uninitialized} {} { target *-*-* } .-1 }
23 ! { dg-note {'sum' was declared here} {} { target *-*-* } .-2 }
24 END SUBROUTINE two
25 end module m2