xref: /llvm-project/flang/test/Parser/OpenMP/allocators-unparse.f90 (revision cdbd22876b71acad9e5eeceadc0d8859e6e73b18)
16311ab21SEthan Luis McDonough! RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp %s | FileCheck --ignore-case %s
26311ab21SEthan Luis McDonough! RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
36311ab21SEthan Luis McDonough! Check unparsing of OpenMP 5.2 Allocators construct
46311ab21SEthan Luis McDonough
56311ab21SEthan Luis McDonoughsubroutine allocate()
66311ab21SEthan Luis McDonough  use omp_lib
76311ab21SEthan Luis McDonough  integer, allocatable :: arr1(:), arr2(:, :)
86311ab21SEthan Luis McDonough
96311ab21SEthan Luis McDonough  !$omp allocators allocate(omp_default_mem_alloc: arr1)
106311ab21SEthan Luis McDonough    allocate(arr1(5))
116311ab21SEthan Luis McDonough
126311ab21SEthan Luis McDonough  !$omp allocators allocate(allocator(omp_default_mem_alloc), align(32): arr1) &
136311ab21SEthan Luis McDonough  !$omp allocate(omp_default_mem_alloc: arr2)
146311ab21SEthan Luis McDonough    allocate(arr1(10), arr2(3, 2))
156311ab21SEthan Luis McDonough
166311ab21SEthan Luis McDonough  !$omp allocators allocate(align(32): arr2)
176311ab21SEthan Luis McDonough    allocate(arr2(5, 3))
186311ab21SEthan Luis McDonoughend subroutine allocate
196311ab21SEthan Luis McDonough
206311ab21SEthan Luis McDonough!CHECK: INTEGER, ALLOCATABLE :: arr1(:), arr2(:,:)
216311ab21SEthan Luis McDonough!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(omp_default_mem_alloc: arr1)
226311ab21SEthan Luis McDonough!CHECK-NEXT: ALLOCATE(arr1(5))
23*cdbd2287SKrzysztof Parzyszek!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALLOCATOR(omp_default_mem_alloc), ALIGN(32): arr1) ALL&
24*cdbd2287SKrzysztof Parzyszek!CHECK-NEXT:!$OMP&OCATE(omp_default_mem_alloc: arr2)
256311ab21SEthan Luis McDonough!CHECK-NEXT: ALLOCATE(arr1(10), arr2(3,2))
266311ab21SEthan Luis McDonough!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALIGN(32): arr2)
276311ab21SEthan Luis McDonough!CHECK-NEXT: ALLOCATE(arr2(5,3))
286311ab21SEthan Luis McDonough
296311ab21SEthan Luis McDonough!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
306311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Verbatim
316311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
32*cdbd2287SKrzysztof Parzyszek!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
336311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
346311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateStmt
356311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Allocation
366311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
376311ab21SEthan Luis McDonough
386311ab21SEthan Luis McDonough!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
396311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Verbatim
406311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
41*cdbd2287SKrzysztof Parzyszek!PARSE-TREE-NEXT: Modifier -> OmpAllocatorComplexModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
42*cdbd2287SKrzysztof Parzyszek!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
436311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
446311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpClause -> Allocate -> OmpAllocateClause
45*cdbd2287SKrzysztof Parzyszek!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
466311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
476311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateStmt
486311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Allocation
496311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
506311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateShapeSpec
516311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '10'
526311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Allocation
536311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
546311ab21SEthan Luis McDonough
556311ab21SEthan Luis McDonough!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
566311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Verbatim
576311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
58*cdbd2287SKrzysztof Parzyszek!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
596311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
606311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateStmt
616311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: Allocation
626311ab21SEthan Luis McDonough!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
63