Fix gcc.c-torture/execute/ieee/cdivchkf.c on hpux
[official-gcc.git] / libgomp / testsuite / libgomp.fortran / allocate-4.f90
blob1f833b6e70f2b2403f1d84a3f51794e4f6e8a179
1 ! { dg-do compile }
4 subroutine test()
5 use iso_c_binding, only: c_intptr_t
6 implicit none
7 integer, parameter :: omp_allocator_handle_kind = 1 !! <<<
8 integer (kind=omp_allocator_handle_kind), &
9 parameter :: omp_high_bw_mem_alloc = 4
10 integer :: q, x,y,z
11 integer, parameter :: cnst(2) = [64, 101]
13 !$omp parallel allocate( omp_high_bw_mem_alloc : x) firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
14 !$omp end parallel
16 !$omp parallel allocate( allocator (omp_high_bw_mem_alloc) : x) firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
17 !$omp end parallel
19 !$omp parallel allocate( align (q) : x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
20 !$omp end parallel
22 !$omp parallel allocate( align (32) : x) firstprivate(x) ! OK
23 !$omp end parallel
25 !$omp parallel allocate( align(q) : x) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
26 !$omp end parallel
28 !$omp parallel allocate( align(cnst(1)) : x ) firstprivate(x) ! OK
29 !$omp end parallel
31 !$omp parallel allocate( align(cnst(2)) : x) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
32 !$omp end parallel
34 !$omp parallel allocate( align( 31) :x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
35 !$omp end parallel
37 !$omp parallel allocate( align (32.0): x) firstprivate(x) ! { dg-error "32:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
38 !$omp end parallel
40 !$omp parallel allocate( align(cnst ) : x ) firstprivate(x) ! { dg-error "31:ALIGN requires a scalar positive constant integer alignment expression at \\(1\\) that is a power of two" }
41 !$omp end parallel
42 end