[Clang] Correctly determine constexprness of dependent lambdas. (#124468)
[llvm-project.git] / flang / test / Parser / OpenMP / task-reduction-clause.f90
blob248ff7918dbe5f75e39ace1514aa64f84eb02251
1 !RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=50 %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
2 !RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=50 %s | FileCheck --check-prefix="PARSE-TREE" %s
4 subroutine f00
5 integer :: x
6 !$omp taskgroup task_reduction(+: x)
7 x = x + 1
8 !$omp end taskgroup
9 end
11 !UNPARSE: SUBROUTINE f00
12 !UNPARSE: INTEGER x
13 !UNPARSE: !$OMP TASKGROUP TASK_REDUCTION(+: x)
14 !UNPARSE: x=x+1_4
15 !UNPARSE: !$OMP END TASKGROUP
16 !UNPARSE: END SUBROUTINE
18 !PARSE-TREE: OmpBeginBlockDirective
19 !PARSE-TREE: | OmpBlockDirective -> llvm::omp::Directive = taskgroup
20 !PARSE-TREE: | OmpClauseList -> OmpClause -> TaskReduction -> OmpTaskReductionClause
21 !PARSE-TREE: | | Modifier -> OmpReductionIdentifier -> DefinedOperator -> IntrinsicOperator = Add
22 !PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
23 !PARSE-TREE: Block