xref: /llvm-project/flang/test/Parser/OpenMP/allocate-tree.f90 (revision 2c93598b32c217c605dc4eeea8e37eae2ba5799a)
1! REQUIRES: openmp_runtime
2
3! RUN: %flang_fc1 %openmp_flags -fdebug-dump-parse-tree %s | FileCheck %s
4! RUN: %flang_fc1 %openmp_flags -fdebug-unparse %s | FileCheck %s --check-prefix="UNPARSE"
5! Ensures associated declarative OMP allocations are nested in their
6! corresponding executable allocate directive
7
8program allocate_tree
9    use omp_lib
10    integer, allocatable :: w, xarray(:), zarray(:, :)
11    integer :: z, t
12    t = 2
13    z = 3
14!$omp allocate(w) allocator(omp_const_mem_alloc)
15!$omp allocate(xarray) allocator(omp_large_cap_mem_alloc)
16!$omp allocate(zarray) allocator(omp_default_mem_alloc)
17!$omp allocate
18    allocate(w, xarray(4), zarray(t, z))
19end program allocate_tree
20
21!CHECK: | | DeclarationConstruct -> SpecificationConstruct -> TypeDeclarationStmt
22!CHECK-NEXT: | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec ->
23!CHECK-NEXT: | | | AttrSpec -> Allocatable
24!CHECK-NEXT: | | | EntityDecl
25!CHECK-NEXT: | | | | Name = 'w'
26!CHECK-NEXT: | | | EntityDecl
27!CHECK-NEXT: | | | | Name = 'xarray'
28!CHECK-NEXT: | | | | ArraySpec -> DeferredShapeSpecList -> int = '1'
29!CHECK-NEXT: | | | EntityDecl
30!CHECK-NEXT: | | | | Name = 'zarray'
31!CHECK-NEXT: | | | | ArraySpec -> DeferredShapeSpecList -> int = '2'
32
33
34!CHECK: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPExecutableAllocate
35!CHECK-NEXT: | | | Verbatim
36!CHECK-NEXT: | | | OmpClauseList ->
37!CHECK-NEXT: | | | OpenMPDeclarativeAllocate
38!CHECK-NEXT: | | | | Verbatim
39!CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'w'
40!CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
41!CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
42!CHECK-NEXT: | | | OpenMPDeclarativeAllocate
43!CHECK-NEXT: | | | | Verbatim
44!CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'xarray'
45!CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
46!CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
47!CHECK-NEXT: | | | OpenMPDeclarativeAllocate
48!CHECK-NEXT: | | | | Verbatim
49!CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'zarray'
50!CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
51!CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
52!CHECK-NEXT: | | | AllocateStmt
53
54!UNPARSE: !$OMP ALLOCATE (w) ALLOCATOR(3_8)
55!UNPARSE-NEXT: !$OMP ALLOCATE (xarray) ALLOCATOR(2_8)
56!UNPARSE-NEXT: !$OMP ALLOCATE (zarray) ALLOCATOR(1_8)
57!UNPARSE-NEXT: !$OMP ALLOCATE
58!UNPARSE-NEXT: ALLOCATE(w, xarray(4_4), zarray(t,z))
59