mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-28 03:16:05 +00:00

This PR adds all the missing semantics for the Linear clause based on the OpenMP 5.2 restrictions. The restriction details are mentioned below. OpenMP 5.2: 5.4.6 linear Clause restrictions - A linear-modifier may be specified as ref or uval only on a declare simd directive. - If linear-modifier is not ref, all list items must be of type integer. - If linear-modifier is ref or uval, all list items must be dummy arguments without the VALUE attribute. - List items must not be Cray pointers or variables that have the POINTER attribute. Cray pointer support has been deprecated. - If linear-modifier is ref, list items must be polymorphic variables, assumed-shape arrays, or variables with the ALLOCATABLE attribute. - A common block name must not appear in a linear clause. - The list-item cannot appear more than once 4.4.4 ordered Clause restriction - If n is explicitly specified, a linear clause must not be specified on the same directive. 5.11 aligned Clause restriction - Each list item must have C_PTR or Cray pointer type or have the POINTER or ALLOCATABLE attribute. Cray pointer support has been deprecated.
42 lines
1.1 KiB
Fortran
42 lines
1.1 KiB
Fortran
! REQUIRES: plugins, examples, shell
|
|
|
|
! RUN: %flang_fc1 -load %llvmshlibdir/flangOmpReport.so -plugin flang-omp-report -fopenmp %s -o - | FileCheck %s
|
|
|
|
! Check OpenMP declarative directives
|
|
|
|
! 2.8.2 declare-simd
|
|
|
|
subroutine declare_simd_1(a, b)
|
|
real(8), intent(inout), allocatable :: a, b
|
|
!$omp declare simd(declare_simd_1) aligned(a)
|
|
a = 3.14 + b
|
|
end subroutine declare_simd_1
|
|
|
|
! 2.10.6 declare-target
|
|
! 2.15.2 threadprivate
|
|
|
|
module m2
|
|
contains
|
|
subroutine foo
|
|
!$omp declare target
|
|
integer, parameter :: N=10000, M=1024
|
|
integer :: i
|
|
real :: Q(N, N), R(N,M), S(M,M)
|
|
end subroutine foo
|
|
end module m2
|
|
|
|
end
|
|
|
|
! CHECK:---
|
|
! CHECK-NEXT:- file: '{{[^"]*}}omp-declarative-directive.f90'
|
|
! CHECK-NEXT: line: 11
|
|
! CHECK-NEXT: construct: declare simd
|
|
! CHECK-NEXT: clauses:
|
|
! CHECK-NEXT: - clause: aligned
|
|
! CHECK-NEXT: details: a
|
|
! CHECK-NEXT:- file: '{{[^"]*}}omp-declarative-directive.f90'
|
|
! CHECK-NEXT: line: 21
|
|
! CHECK-NEXT: construct: declare target
|
|
! CHECK-NEXT: clauses: []
|
|
! CHECK-NEXT:...
|