Skip to content

Commit

Permalink
test: add two more test cases for loop metadata
Browse files Browse the repository at this point in the history
Those two test cases were supposed to be contributed to PR #1094.
Unfortunately, at that time, the -emit-flang-llvm flag was not
supported by the frontend driver yet.

One of those tests was failing make-check testing. It turned out,
flang failed to recognize one of the loops. A small change had to
be backported in order to improve the situation.

Signed-off-by: Paul Osmialowski <[email protected]>
  • Loading branch information
pawosm-arm committed Jun 9, 2022
1 parent 60eff21 commit e369aab
Show file tree
Hide file tree
Showing 4 changed files with 214 additions and 6 deletions.
60 changes: 60 additions & 0 deletions test/llvm_ir_correct/loop-line-metadata.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,60 @@
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
! See https://llvm.org/LICENSE.txt for license information.
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception

! REQUIRES: llvm-13

! RUN: %flang -g -O2 -emit-flang-llvm %s -o /dev/stdout | FileCheck %s

! Test that with debug metadata enabled, in the absence of loop pragmas, loops
! get annotated with their start and end line numbers.

! CHECK: test_loop_line_md
subroutine test_loop_line_md(x, N)
integer, intent(out) :: x

do i = 1, N
! CHECK-DAG: ![[L1Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-DAG: ![[L1End:[0-9]+]] = !DILocation(line: [[@LINE+4]],
x = x + i + 1
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L1:[0-9]+]]
! CHECK-DAG: ![[L1]] = !{ ![[L1]],{{.*}}![[L1Start]], ![[L1End]]
end do

do i = 1, N
! CHECK-DAG: ![[L2Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-DAG: ![[L2End:[0-9]+]] = !DILocation(line: [[@LINE+11]],

do j = 1, N
! CHECK-DAG: ![[L3Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-DAG: ![[L3End:[0-9]+]] = !DILocation(line: [[@LINE+4]],
x = x + j + i + 1
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L3:[0-9]+]]
! CHECK-DAG: ![[L3]] = !{ ![[L3]],{{.*}}![[L3Start]], ![[L3End]]
end do
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L2:[0-9]+]]
! CHECK-DAG: ![[L2]] = !{ ![[L2]],{{.*}}![[L2Start]], ![[L2End]]
end do

! There should be no further loop metadata.
! CHECK-NOT: !llvm.loop
end subroutine

! CHECK: test_implicit_loop_intrinsic
subroutine test_implicit_loop_intrinsic(x, arr)
integer :: arr(:)
integer, intent(out) :: x
x = sum(arr)
! NOTE: You might expect this to have an llvm.loop, but it does not at the
! moment, because the loop does not get marked with BIH_HEAD.
! CHECK-NOT: !llvm.loop
end subroutine

! CHECK: test_implicit_loop_array_op
subroutine test_implicit_loop_array_op(arr)
integer :: arr(:)
arr = 3
! NOTE: You might expect this to have an llvm.loop, but it does not at the
! moment, because the loop does not get marked with BIH_HEAD.
! CHECK-NOT: !llvm.loop
end subroutine
150 changes: 150 additions & 0 deletions test/llvm_ir_correct/loop-pragmas-and-line-metadata.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,150 @@
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
! See https://llvm.org/LICENSE.txt for license information.
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception

! REQUIRES: llvm-13

! RUN: %flang -g -fopenmp -O2 -emit-flang-llvm %s -o /dev/stdout \
! RUN: | FileCheck --check-prefixes=CHECK,CHECK-LINE %s

! RUN: %flang -g -fopenmp -O2 -emit-flang-llvm %s -o /dev/stdout \
! RUN: | FileCheck --check-prefixes=CHECK,CHECK-DIRS %s

! Test that loop metadata is correct for a variety of loops.
!
! This file tests two properties of the metadata:
!
! * CHECK -LINE: Check the line number metadata associated with the loop refers
! to the correct source lines.
! * CHECK -DIRS: Check that directives associated with the loop are the correct ones.
!
! This is done as two separate runs to avoid being sensitive to the order of
! metadata nodes within the loop ID.
!
! The strategy is to locate the DILocation nodes for the start and end of the
! loop using @LINE, then locate the !llvm.loop node on a branch, then check
! that the contents of the loop ID are as expected.
!
! The test also enforces that the expected number of !llvm.loop directives are
! present.

! CHECK: test_loop_line_md
subroutine test_loop_line_md(x, N)
integer, intent(out) :: x

! CHECK-DIRS-DAG: ![[VEC_ON:[0-9]+]] = !{ !"llvm.loop.vectorize.enable", i1 1 }
! CHECK-DIRS-DAG: ![[VEC_OFF:[0-9]+]] = !{ !"llvm.loop.vectorize.enable", i1 0 }
! CHECK-DIRS-DAG: ![[UNROLL_ON:[0-9]+]] = !{ !"llvm.loop.unroll.enable" }
! CHECK-DIRS-DAG: ![[UNROLL_OFF:[0-9]+]] = !{ !"llvm.loop.unroll.disable" }

!dir$ novector
do i = 1, N
! CHECK-LINE-DAG: ![[L1Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L1End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L1:[0-9]+]]
! CHECK-LINE-DAG: ![[L1]] = !{ ![[L1]],{{.*}}![[L1Start]], ![[L1End]]
! CHECK-DIRS-DAG: ![[L1]] = !{ ![[L1]],{{.*}}![[VEC_OFF]]{{[, ]}}
end do

!dir$ vector always
do i = 1, Nq
! CHECK-LINE-DAG: ![[L2Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L2End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L2:[0-9]+]]
! CHECK-LINE-DAG: ![[L2]] = !{ ![[L2]],{{.*}}![[L2Start]], ![[L2End]]
! CHECK-DIRS-DAG: ![[L2]] = !{ ![[L2]],{{.*}}![[VEC_ON]]{{[, ]}}
end do

!dir$ nounroll
do i = 1, N
! CHECK-LINE-DAG: ![[L3Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L3End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L3:[0-9]+]]
! CHECK-LINE-DAG: ![[L3]] = !{ ![[L3]],{{.*}}![[L3Start]], ![[L3End]],
! CHECK-DIRS-DAG: ![[L3]] = !{ ![[L3]],{{.*}}![[UNROLL_OFF]]{{[, ]}}
end do

!dir$ unroll
do i = 1, N
! CHECK-LINE-DAG: ![[L4Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L4End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L4:[0-9]+]]
! CHECK-LINE-DAG: ![[L4]] = !{ ![[L4]],{{.*}}![[L4Start]], ![[L4End]],
! CHECK-DIRS-DAG: ![[L4]] = !{ ![[L4]],{{.*}}![[UNROLL_ON]]{{[, ]}}
end do

!dir$ nounroll
do i = 1, N
! CHECK-LINE-DAG: ![[L5Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L5End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L5:[0-9]+]]
! CHECK-LINE-DAG: ![[L5]] = !{ ![[L5]],{{.*}}![[L5Start]], ![[L5End]],
! CHECK-DIRS-DAG: ![[L5]] = !{ ![[L5]],{{.*}}![[UNROLL_OFF]]{{[, ]}}
end do

!dir$ unroll
do i = 1, N
! CHECK-LINE-DAG: ![[L5Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L5End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L5:[0-9]+]]
! CHECK-LINE-DAG: ![[L5]] = !{ ![[L5]],{{.*}}![[L5Start]], ![[L5End]],
! CHECK-DIRS-DAG: ![[L5]] = !{ ![[L5]],{{.*}}![[UNROLL_ON]]{{[, ]}}
end do

!$omp simd
do i = 1, N
! CHECK-LINE-DAG: ![[L7Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L7End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L7:[0-9]+]]
! CHECK-LINE-DAG: ![[L7]] = !{ ![[L7]],{{.*}}![[L7Start]], ![[L7End]]
! CHECK-DIRS-DAG: ![[L7]] = !{ ![[L7]],{{.*}}![[VEC_ON]]{{[, ]}}
end do

!dir$ novector
do i = 1, N
! CHECK-LINE-DAG: ![[L8Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L8End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: This test is missing the redundant llvm.loop instruction because the
! previous one uses the !$omp simd directive. This is weird.
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L8:[0-9]+]]
! CHECK-LINE-DAG: ![[L8]] = !{ ![[L8]],{{.*}}![[L8Start]], ![[L8End]]
! CHECK-DIRS-DAG: ![[L8]] = !{ ![[L8]],{{.*}}![[VEC_OFF]]{{[, ]}}
end do

!dir$ vector always
do i = 1, N
! CHECK-LINE-DAG: ![[L9Start:[0-9]+]] = !DILocation(line: [[@LINE-1]],
! CHECK-LINE-DAG: ![[L9End:[0-9]+]] = !DILocation(line: [[@LINE+7]],
x = x + i + 1
! NOTE: The first one of these is redundant.
! CHECK-DAG: br {{.*}}, !llvm.loop !{{[0-9]+}}
! CHECK-DAG: br {{.*}}, !llvm.loop ![[L9:[0-9]+]]
! CHECK-LINE-DAG: ![[L9]] = !{ ![[L9]],{{.*}}![[L9Start]], ![[L9End]]
! CHECK-DIRS-DAG: ![[L9]] = !{ ![[L9]],{{.*}}![[VEC_ON]]{{[, ]}}
end do

! There should be no further loop metadata.
! CHECK-NOT: !llvm.loop
end subroutine
9 changes: 3 additions & 6 deletions tools/flang2/flang2exe/cgmain.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1800,12 +1800,9 @@ schedule(void)
(void)cons_vec_always_metadata();
}
if ((check_for_loop_directive(ILT_LINENO(ilt), 191, 0x4))) {
LL_MDRef loop_md = cons_vec_always_metadata();
INSTR_LIST *i = find_last_executable(llvm_info.last_instr);
if (i) {
i->flags |= LOOP_BACKEDGE_FLAG;
i->misc_metadata = loop_md;
}
if (LL_MDREF_IS_NULL(loop_md))
loop_md = cons_loop_id_md();
(void)cons_vec_always_metadata();
}

if (BIH_VECTORLENGTH_ENABLED(bih)) {
Expand Down
1 change: 1 addition & 0 deletions tools/shared/pragma.c
Original file line number Diff line number Diff line change
Expand Up @@ -723,6 +723,7 @@ do_sw(void)
assn(DIR_OFFSET(currdir, x[235]), num);
} else if (strcmp(ctok, "always") == 0) {
bclr(DIR_OFFSET(currdir, x[19]), 0x18);
bset(DIR_OFFSET(currdir, x[19]), 0x400);
bset(DIR_OFFSET(currdir, x[191]), 0x4);
} else {
backup_nowarn = gbl.nowarn;
Expand Down

0 comments on commit e369aab

Please sign in to comment.