Again, this simplifies the semantic checks and lowering quite a bit. Update the check for positive alignment to use a more informative message, and to highlight the modifier itsef, not the whole clause. Remove the checks for the allocator expression itself being positive: there is nothing in the spec that says that it should be positive. Remove the "simple" modifier from the AllocateT template, since both simple and complex modifiers are the same thing, only differing in syntax.
63 lines
3.3 KiB
Fortran
63 lines
3.3 KiB
Fortran
! RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp %s | FileCheck --ignore-case %s
|
|
! RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
|
|
! Check unparsing of OpenMP 5.2 Allocators construct
|
|
|
|
subroutine allocate()
|
|
use omp_lib
|
|
integer, allocatable :: arr1(:), arr2(:, :)
|
|
|
|
!$omp allocators allocate(omp_default_mem_alloc: arr1)
|
|
allocate(arr1(5))
|
|
|
|
!$omp allocators allocate(allocator(omp_default_mem_alloc), align(32): arr1) &
|
|
!$omp allocate(omp_default_mem_alloc: arr2)
|
|
allocate(arr1(10), arr2(3, 2))
|
|
|
|
!$omp allocators allocate(align(32): arr2)
|
|
allocate(arr2(5, 3))
|
|
end subroutine allocate
|
|
|
|
!CHECK: INTEGER, ALLOCATABLE :: arr1(:), arr2(:,:)
|
|
!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(omp_default_mem_alloc: arr1)
|
|
!CHECK-NEXT: ALLOCATE(arr1(5))
|
|
!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALLOCATOR(omp_default_mem_alloc), ALIGN(32): arr1) ALL&
|
|
!CHECK-NEXT:!$OMP&OCATE(omp_default_mem_alloc: arr2)
|
|
!CHECK-NEXT: ALLOCATE(arr1(10), arr2(3,2))
|
|
!CHECK-NEXT:!$OMP ALLOCATE ALLOCATE(ALIGN(32): arr2)
|
|
!CHECK-NEXT: ALLOCATE(arr2(5,3))
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
|
|
!PARSE-TREE-NEXT: Verbatim
|
|
!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
|
|
!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
|
|
!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
|
|
!PARSE-TREE-NEXT: AllocateStmt
|
|
!PARSE-TREE-NEXT: Allocation
|
|
!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
|
|
!PARSE-TREE-NEXT: Verbatim
|
|
!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
|
|
!PARSE-TREE-NEXT: Modifier -> OmpAllocatorComplexModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
|
|
!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
|
|
!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr1'
|
|
!PARSE-TREE-NEXT: OmpClause -> Allocate -> OmpAllocateClause
|
|
!PARSE-TREE-NEXT: Modifier -> OmpAllocatorSimpleModifier -> Scalar -> Integer -> Expr -> Designator -> DataRef -> Name = 'omp_default_mem_alloc'
|
|
!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
|
|
!PARSE-TREE-NEXT: AllocateStmt
|
|
!PARSE-TREE-NEXT: Allocation
|
|
!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr1'
|
|
!PARSE-TREE-NEXT: AllocateShapeSpec
|
|
!PARSE-TREE-NEXT: Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '10'
|
|
!PARSE-TREE-NEXT: Allocation
|
|
!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPAllocatorsConstruct
|
|
!PARSE-TREE-NEXT: Verbatim
|
|
!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Allocate -> OmpAllocateClause
|
|
!PARSE-TREE-NEXT: Modifier -> OmpAlignModifier -> Scalar -> Integer -> Expr -> LiteralConstant -> IntLiteralConstant = '32'
|
|
!PARSE-TREE-NEXT: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'arr2'
|
|
!PARSE-TREE-NEXT: AllocateStmt
|
|
!PARSE-TREE-NEXT: Allocation
|
|
!PARSE-TREE-NEXT: AllocateObject -> Name = 'arr2'
|