tree-optimization/113385 - wrong loop father with early exit vectorization
[official-gcc.git] / gcc / testsuite / gfortran.dg / gomp / allocate-2.f90
blobcc83b5edbce6b9cd3ac7f4c421d3a5fff291c991
1 ! { dg-do compile }
3 module omp_lib_kinds
4 use iso_c_binding, only: c_int, c_intptr_t
5 implicit none
6 private :: c_int, c_intptr_t
7 integer, parameter :: omp_allocator_handle_kind = c_intptr_t
9 end module
11 subroutine foo(x)
12 use omp_lib_kinds
13 implicit none
14 integer :: x
16 !$omp task allocate (x) ! { dg-error "'x' specified in 'allocate' clause at .1. but not in an explicit privatization clause" }
17 x=1
18 !$omp end task
20 !$omp parallel allocate (x) ! { dg-error "'x' specified in 'allocate' clause at .1. but not in an explicit privatization clause" }
21 x=2
22 !$omp end parallel
24 !$omp parallel allocate (x) shared (x) ! { dg-error "'x' specified in 'allocate' clause at .1. but not in an explicit privatization clause" }
25 x=3
26 !$omp end parallel
28 !$omp parallel private (x) allocate (x) allocate (x) ! { dg-warning "'x' appears more than once in 'allocate' at .1." }
29 x=4
30 !$omp end parallel
32 !$omp parallel private (x) allocate (x, x) ! { dg-warning "'x' appears more than once in 'allocate' at .1." }
33 x=5
34 !$omp end parallel
36 !$omp parallel allocate (0_1: x) private(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind at .1." }
37 x=6
38 !$omp end parallel
40 !$omp parallel private (x) allocate (0.1 : x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind at .1." }
41 x=7
42 !$omp end parallel
44 end subroutine