xref: /llvm-project/flang/test/Parser/OpenMP/allocators-unparse.f90 (revision cdbd22876b71acad9e5eeceadc0d8859e6e73b18)
1! RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp %s | FileCheck --ignore-case %s
2! RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
3! Check unparsing of OpenMP 5.2 Allocators construct
4
5subroutine allocate()
6  use omp_lib
7  integer, allocatable :: arr1(:), arr2(:, :)
8
9  !$omp allocators allocate(omp_default_mem_alloc: arr1)
10    allocate(arr1(5))
11
12  !$omp allocators allocate(allocator(omp_default_mem_alloc), align(32): arr1) &
13  !$omp allocate(omp_default_mem_alloc: arr2)
14    allocate(arr1(10), arr2(3, 2))
15
16  !$omp allocators allocate(align(32): arr2)
17    allocate(arr2(5, 3))
18end subroutine allocate
19
20!CHECK: INTEGER, ALLOCATABLE :: arr1(:), arr2(:,:)
21!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(omp_default_mem_alloc: arr1)
22!CHECK-NEXT: ALLOCATE(arr1(5))
23!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALLOCATOR(omp_default_mem_alloc), ALIGN(32): arr1) ALL&
24!CHECK-NEXT:!$OMP&OCATE(omp_default_mem_alloc: arr2)
25!CHECK-NEXT: ALLOCATE(arr1(10), arr2(3,2))
26!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALIGN(32): arr2)
27!CHECK-NEXT: ALLOCATE(arr2(5,3))
28
29!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
30!PARSE-TREE-NEXT: Verbatim
31!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
32!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
33!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
34!PARSE-TREE-NEXT: AllocateStmt
35!PARSE-TREE-NEXT: Allocation
36!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
37
38!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
39!PARSE-TREE-NEXT: Verbatim
40!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
41!PARSE-TREE-NEXT: Modifier -> OmpAllocatorComplexModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
42!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
43!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
44!PARSE-TREE-NEXT: OmpClause -> Allocate -> OmpAllocateClause
45!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
46!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
47!PARSE-TREE-NEXT: AllocateStmt
48!PARSE-TREE-NEXT: Allocation
49!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
50!PARSE-TREE-NEXT: AllocateShapeSpec
51!PARSE-TREE-NEXT: Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '10'
52!PARSE-TREE-NEXT: Allocation
53!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
54
55!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
56!PARSE-TREE-NEXT: Verbatim
57!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
58!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
59!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
60!PARSE-TREE-NEXT: AllocateStmt
61!PARSE-TREE-NEXT: Allocation
62!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
63