tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / assumes-1.f90
blob3d468dc1c812dcd2c615517c88f7debf466903cb
1 ! All of the following (up to PROGRAM) are okay:
3 subroutine sub
4 interface
5 subroutine sub_iterface()
6 !$omp assumes no_openmp_routines absent(simd) ! OK inferface of an external subroutine/subprogram
7 end
8 end interface
9 !$omp assumes no_openmp_routines absent(simd) ! OK external subroutine/subprogram
10 contains
11 subroutine inner_sub
12 !$omp assumes no_parallelism absent(teams) ! OK internal subroutine/subprogram
13 end
14 end
16 integer function func ()
17 !$omp assumes no_openmp_routines absent(simd) ! OK external function/subprogram
18 interface
19 integer function func_iterface()
20 !$omp assumes no_openmp_routines absent(simd) ! OK inferface of an external function/subprogram
21 end
22 end interface
23 func = 0
24 contains
25 integer function inner_func()
26 !$omp assumes no_parallelism absent(teams) ! OK internal function/subprogram
27 inner_sub2 = 0
28 end
29 end
31 module m
32 integer ::x
33 !$omp assumes contains(target) holds(x > 0.0)
35 interface
36 subroutine mod_mod_sub_iterface()
37 !$omp assumes no_openmp_routines absent(simd) ! OK inferface of an external subroutine/subprogram
38 end
39 integer function mod_mod_func_iterface()
40 !$omp assumes no_openmp_routines absent(error) ! OK inferface of an external subroutine/subprogram
41 end
42 end interface
44 contains
45 subroutine mod_sub
46 interface
47 subroutine mod_sub_iterface()
48 !$omp assumes no_openmp_routines absent(simd) ! OK inferface of an external subroutine/subprogram
49 end
50 end interface
51 !$omp assumes no_openmp_routines absent(simd) ! OK module subroutine/subprogram
52 contains
53 subroutine mod_inner_sub
54 !$omp assumes no_parallelism absent(teams) ! OK internal subroutine/subprogram
55 end
56 end
58 integer function mod_func ()
59 !$omp assumes no_openmp_routines absent(simd) ! OK module function/subprogram
60 interface
61 integer function mod_func_iterface()
62 !$omp assumes no_openmp_routines absent(simd) ! OK inferface of an external function/subprogram
63 end
64 end interface
65 mod_func = 0
66 contains
67 integer function mod_inner_func()
68 !$omp assumes no_parallelism absent(teams) ! OK internal function/subprogram
69 mod_inner_sub2 = 0
70 end
71 end
72 end module m
75 ! PROGRAM - invalid as:
76 ! main program is a program unit that is not a subprogram
77 !$omp assumes no_openmp absent(simd) ! { dg-error "must be in the specification part of a subprogram or module" }
78 block
79 ! invalid: block
80 !$omp assumes no_openmp absent(target) ! { dg-error "must be in the specification part of a subprogram or module" }
81 end block
82 end