[LVI][CVP] Add test for trunc bittest. (NFC)
[llvm-project.git] / flang / test / Parser / OpenMP / allocate-unparse.f90
blob94bc2adf35ea91a83110ef90299b4a3158bce359
1 ! RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp %s | FileCheck %s
2 ! Check Unparsing of OpenMP Allocate directive
4 program allocate_unparse
5 use omp_lib
7 real, dimension (:,:), allocatable :: darray
8 integer :: a, b, j, m, n, t, x, y, z
10 ! 2.11.3 declarative allocate
12 !$omp allocate(x, y)
13 !$omp allocate(x, y) allocator(omp_default_mem_alloc)
15 ! 2.11.3 executable allocate
17 !$omp allocate(a, b)
18 allocate ( darray(a, b) )
19 !$omp allocate allocator(omp_default_mem_alloc)
20 allocate ( darray(a, b) )
21 !$omp allocate(a, b) allocator(omp_default_mem_alloc)
22 allocate ( darray(a, b) )
24 !$omp allocate(t) allocator(omp_const_mem_alloc)
25 !$omp allocate(z) allocator(omp_default_mem_alloc)
26 !$omp allocate(m) allocator(omp_default_mem_alloc)
27 !$omp allocate(n)
28 !$omp allocate(j) align(16)
29 allocate ( darray(z, t) )
31 end program allocate_unparse
33 !CHECK:!$OMP ALLOCATE (x,y)
34 !CHECK:!$OMP ALLOCATE (x,y) ALLOCATOR(omp_default_mem_alloc)
35 !CHECK:!$OMP ALLOCATE (a,b)
36 !CHECK:ALLOCATE(darray(a,b))
37 !CHECK:!$OMP ALLOCATE ALLOCATOR(omp_default_mem_alloc)
38 !CHECK:ALLOCATE(darray(a,b))
39 !CHECK:!$OMP ALLOCATE (a,b) ALLOCATOR(omp_default_mem_alloc)
40 !CHECK:ALLOCATE(darray(a,b))
41 !CHECK:!$OMP ALLOCATE (t) ALLOCATOR(omp_const_mem_alloc)
42 !CHECK:!$OMP ALLOCATE (z) ALLOCATOR(omp_default_mem_alloc)
43 !CHECK:!$OMP ALLOCATE (m) ALLOCATOR(omp_default_mem_alloc)
44 !CHECK:!$OMP ALLOCATE (n)
45 !CHECK:!$OMP ALLOCATE (j) ALIGN(16)
46 !CHECK:ALLOCATE(darray(z,t))