llvm-project/flang/test/Lower/OpenMP/task-depend-structure-component.f90
Kareem Ergawy f5d3470d42
[flang][OpenMP] Allow structure component in task depend clauses (#141923)
Even though the spec (version 5.2) prohibits strcuture components from
being specified in `depend` clauses, this restriction is not sensible.

This PR rectifies the issue by lifting that restriction and allowing
structure components in `depend` clauses (which is allowed by OpenMP
6.0).
2025-05-30 06:22:29 +02:00

22 lines
622 B
Fortran

! RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s
subroutine depend
type :: my_struct
integer :: my_component(10)
end type
type(my_struct) :: my_var
!$omp task depend(in:my_var%my_component)
!$omp end task
end subroutine depend
! CHECK: %[[VAR_ALLOC:.*]] = fir.alloca !fir.type<{{.*}}my_struct{{.*}}> {bindc_name = "my_var", {{.*}}}
! CHECK: %[[VAR_DECL:.*]]:2 = hlfir.declare %[[VAR_ALLOC]]
! CHECK: %[[COMP_SELECTOR:.*]] = hlfir.designate %[[VAR_DECL]]#0{"my_component"}
! CHECK: omp.task depend(taskdependin -> %[[COMP_SELECTOR]] : {{.*}}) {
! CHECK: omp.terminator
! CHECK: }