1 ! REQUIRES: openmp_runtime
3 ! RUN: %flang_fc1 %openmp_flags -fdebug-dump-parse-tree %s | FileCheck %s
4 ! Ensures associated declarative OMP allocations in the specification
9 integer, allocatable
:: w
, xarray(:), zarray(:, :)
11 !$omp allocate(f) allocator(omp_default_mem_alloc)
13 !$omp allocate(w) allocator(omp_const_mem_alloc)
14 !$omp allocate(xarray) allocator(omp_large_cap_mem_alloc)
15 !$omp allocate(zarray) allocator(omp_default_mem_alloc)
17 allocate (w
, xarray(4), zarray(5, f
))
18 end program allocate_tree
20 !CHECK: | | DeclarationConstruct -> SpecificationConstruct -> OpenMPDeclarativeConstruct -> OpenMPDeclarativeAllocate
21 !CHECK-NEXT: | | | Verbatim
22 !CHECK-NEXT: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'f'
23 !CHECK-NEXT: | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
24 !CHECK-NEXT: | | | | Designator -> DataRef -> Name =
25 !CHECK-NEXT: | ExecutionPart -> Block
26 !CHECK-NEXT: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'f=2_4'
27 !CHECK-NEXT: | | | Variable = 'f'
28 !CHECK-NEXT: | | | | Designator -> DataRef -> Name = 'f'
29 !CHECK-NEXT: | | | Expr = '2_4'
30 !CHECK-NEXT: | | | | LiteralConstant -> IntLiteralConstant = '2'
31 !CHECK-NEXT: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPExecutableAllocate
32 !CHECK-NEXT: | | | Verbatim
33 !CHECK-NEXT: | | | OmpClauseList ->
34 !CHECK-NEXT: | | | OpenMPDeclarativeAllocate
35 !CHECK-NEXT: | | | | Verbatim
36 !CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'w'
37 !CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
38 !CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
39 !CHECK-NEXT: | | | OpenMPDeclarativeAllocate
40 !CHECK-NEXT: | | | | Verbatim
41 !CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'xarray'
42 !CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
43 !CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
44 !CHECK-NEXT: | | | OpenMPDeclarativeAllocate
45 !CHECK-NEXT: | | | | Verbatim
46 !CHECK-NEXT: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'zarray'
47 !CHECK-NEXT: | | | | OmpClauseList -> OmpClause -> Allocator -> Scalar -> Integer -> Expr =
48 !CHECK-NEXT: | | | | | Designator -> DataRef -> Name =
49 !CHECK-NEXT: | | | AllocateStmt