[RISCV][SLEEF]: Support SLEEF vector library for RISC-V target. (#114014)
[llvm-project.git] / flang / test / Lower / OpenMP / infinite-loop-in-construct.f90
blob16b400a23186097a9f5cac3b14b4fef0b735762f
1 ! RUN: bbc -fopenmp -o - %s | FileCheck %s
3 ! Check that this test can be lowered successfully.
4 ! See https://github.com/llvm/llvm-project/issues/74348
6 ! CHECK-LABEL: func.func @_QPsb
7 ! CHECK: omp.parallel
8 ! CHECK: cf.cond_br %{{[0-9]+}}, ^bb1, ^bb2
9 ! CHECK-NEXT: ^bb1: // pred: ^bb0
10 ! CHECK: cf.br ^bb2
11 ! CHECK-NEXT: ^bb2: // 3 preds: ^bb0, ^bb1, ^bb2
12 ! CHECK-NEXT: cf.br ^bb2
13 ! CHECK-NEXT: }
15 subroutine sb(ninter, numnod)
16 integer :: ninter, numnod
17 integer, dimension(:), allocatable :: indx_nm
19 !$omp parallel
20 if (ninter>0) then
21 allocate(indx_nm(numnod))
22 endif
23 220 continue
24 goto 220
25 !$omp end parallel
26 end subroutine