xref: /llvm-project/flang/test/Lower/OpenMP/PFT/pre-fir-tree-loop.f90 (revision 0838e33483971e58424802d793e787ed8a3df36b)
1! RUN: bbc -fopenmp -pft-test -o %t %s | FileCheck %s
2! RUN: %flang_fc1 -fopenmp -fdebug-dump-pft -o %t %s | FileCheck %s
3
4! Loop constructs always have an `end do` which can be the target of
5! a branch. So OpenMP loop constructs do not need an artificial
6! continue inserted for a target.
7
8!CHECK-LABEL: sb0
9!CHECK-NOT: continue
10subroutine sb0(cond)
11  implicit none
12  logical :: cond
13  integer :: i
14  !$omp parallel do
15  do i = 1, 20
16    if( cond) then
17      cycle
18    end if
19  end do
20  return
21end subroutine
22
23!CHECK-LABEL: sb1
24!CHECK-NOT: continue
25subroutine sb1(cond)
26  implicit none
27  logical :: cond
28  integer :: i
29  !$omp parallel do
30  do i = 1, 20
31    if( cond) then
32      cycle
33    end if
34  end do
35  !$omp end parallel do
36  return
37end subroutine
38
39!CHECK-LABEL: sb2
40!CHECK-NOT: continue
41subroutine sb2
42  integer :: i, n
43  integer :: tmp
44
45  !$omp parallel do
46  do ifld=1,n
47     do isum=1,n
48       if (tmp > n) then
49         exit
50       endif
51     enddo
52     tmp = n
53  enddo
54end subroutine
55
56!CHECK-LABEL: sb3
57!CHECK-NOT: continue
58subroutine sb3
59  integer :: i, n
60  integer :: tmp
61
62  !$omp parallel do
63  do ifld=1,n
64     do isum=1,n
65       if (tmp > n) then
66         exit
67       endif
68     enddo
69  enddo
70end subroutine
71