aboutsummaryrefslogtreecommitdiff
path: root/libgomp/testsuite/libgomp.fortran/allocate-4.f90
blob: 1f833b6e70f2b2403f1d84a3f51794e4f6e8a179 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
! { dg-do compile }


subroutine test()
use iso_c_binding, only: c_intptr_t
implicit none
integer, parameter :: omp_allocator_handle_kind = 1 !! <<<
integer (kind=omp_allocator_handle_kind), &
                 parameter :: omp_high_bw_mem_alloc = 4
integer :: q, x,y,z
integer, parameter :: cnst(2) = [64, 101]

!$omp parallel allocate( omp_high_bw_mem_alloc : x)  firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
!$omp end parallel

!$omp parallel allocate( allocator (omp_high_bw_mem_alloc) : x)  firstprivate(x) ! { dg-error "Expected integer expression of the 'omp_allocator_handle_kind' kind" }
!$omp end parallel

!$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" }
!$omp end parallel

!$omp parallel allocate( align (32) : x)  firstprivate(x) ! OK
!$omp end parallel

!$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" }
!$omp end parallel

!$omp parallel allocate( align(cnst(1)) : x ) firstprivate(x) ! OK
!$omp end parallel

!$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" }
!$omp end parallel

!$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" }
!$omp end parallel

!$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" }
!$omp end parallel

!$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" }
!$omp end parallel
end