[Clang] Correctly determine constexprness of dependent lambdas. (#124468)
[llvm-project.git] / flang / test / Parser / OpenMP / allocate-align-tree.f90
blob8cb009dfe46c8be3180bf3a3a34be630527ff55d
1 ! REQUIRES: openmp_runtime
3 ! RUN: %flang_fc1 %openmp_flags -fopenmp-version=51 -fdebug-dump-parse-tree %s | FileCheck %s
4 ! RUN: %flang_fc1 %openmp_flags -fdebug-unparse -fopenmp-version=51 %s | FileCheck %s --check-prefix="UNPARSE"
5 ! Ensures associated declarative OMP allocations are nested in their
6 ! corresponding executable allocate directive
8 program allocate_align_tree
9 use omp_lib
10 integer, allocatable :: j(:), xarray(:)
11 integer :: z, t
12 t = 2
13 z = 3
14 !$omp allocate(j) align(16)
15 !$omp allocate(xarray) align(32) allocator(omp_large_cap_mem_alloc)
16 allocate(j(z), xarray(t))
17 end program allocate_align_tree
19 !CHECK: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
20 !CHECK-NEXT: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec ->
21 !CHECK-NEXT: | | | AttrSpec -> Allocatable
22 !CHECK-NEXT: | | | EntityDecl
23 !CHECK-NEXT: | | | | Name = 'j'
26 !CHECK: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPExecutableAllocate
27 !CHECK-NEXT: | | | Verbatim
28 !CHECK-NEXT: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'xarray'
29 !CHECK-NEXT: | | | OmpClauseList -> OmpClause -> Align -> OmpAlignClause -> Scalar -> Integer -> Expr = '32_4'
30 !CHECK-NEXT: | | | | LiteralConstant -> IntLiteralConstant = '32'
31 !CHECK-NEXT: | | | OmpClause -> Allocator -> Scalar -> Integer -> Expr = '2_8'
32 !CHECK-NEXT: | | | | Designator -> DataRef -> Name = 'omp_large_cap_mem_alloc'
33 !CHECK-NEXT: | | | OpenMPDeclarativeAllocate
34 !CHECK-NEXT: | | | | Verbatim
35 !CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'j'
36 !CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Align -> OmpAlignClause -> Scalar -> Integer -> Expr = '16_4'
37 !CHECK-NEXT: | | | | | LiteralConstant -> IntLiteralConstant = '16'
38 !CHECK-NEXT: | | | AllocateStmt
40 !UNPARSE: !$OMP ALLOCATE (j) ALIGN(16_4)
41 !UNPARSE: !$OMP ALLOCATE (xarray) ALIGN(32_4) ALLOCATOR(2_8)
42 !UNPARSE-NEXT: ALLOCATE(j(z), xarray(t))