[clang][bytecode] Implement __builtin_reduce_mul (#118287)
[llvm-project.git] / flang / test / Driver / optimization-remark.f90
blobe90baa892f46a014a673938883ca7c5ed90dad04
1 ! This file tests the -Rpass family of flags (-Rpass, -Rpass-missed
2 ! and -Rpass-analysis)
3 ! loop-delete isn't enabled at O0 so we use at least O1
5 ! DEFINE: %{output} = -emit-llvm -flang-deprecated-no-hlfir -o /dev/null 2>&1
7 ! Check fc1 can handle -Rpass
8 ! RUN: %flang_fc1 %s -O1 -Rpass %{output} 2>&1 | FileCheck %s --check-prefix=REMARKS
10 ! Check that we can override -Rpass= with -Rno-pass.
11 ! RUN: %flang_fc1 %s -O1 -Rpass -Rno-pass %{output} 2>&1 | FileCheck %s --allow-empty --check-prefix=NO-REMARKS
13 ! Check -Rno-pass, -Rno-pass-analysis, -Rno-pass-missed nothing emitted
14 ! RUN: %flang %s -O1 -Rno-pass -S %{output} 2>&1 | FileCheck %s --allow-empty --check-prefix=NO-REMARKS
15 ! RUN: %flang %s -O1 -Rno-pass-missed -S %{output} 2>&1 | FileCheck %s --allow-empty --check-prefix=NO-REMARKS
16 ! RUN: %flang %s -O1 -Rno-pass-analysis -S %{output} 2>&1 | FileCheck %s --allow-empty --check-prefix=NO-REMARKS
18 ! Check valid -Rpass regex
19 ! RUN: %flang %s -O1 -Rpass=loop -S %{output} 2>&1 | FileCheck %s --check-prefix=PASS-REGEX-LOOP-ONLY
21 ! Check valid -Rpass-missed regex
22 ! RUN: %flang %s -O1 -Rpass-missed=loop -S %{output} 2>&1 | FileCheck %s --check-prefix=MISSED-REGEX-LOOP-ONLY
24 ! Check valid -Rpass-analysis regex
25 ! RUN: %flang %s -O1 -Rpass-analysis=loop -S %{output} 2>&1 | FileCheck %s --check-prefix=ANALYSIS-REGEX-LOOP-ONLY
27 ! Check full -Rpass message is emitted
28 ! RUN: %flang %s -O1 -Rpass -S %{output} 2>&1 | FileCheck %s --check-prefix=PASS
30 ! Check full -Rpass-missed message is emitted
31 ! RUN: %flang %s -O1 -Rpass-missed -S %{output} 2>&1 | FileCheck %s --check-prefix=MISSED
33 ! Check full -Rpass-analysis message is emitted
34 ! RUN: %flang %s -O1 -Rpass-analysis -S -o /dev/null 2>&1 | FileCheck %s --check-prefix=ANALYSIS
36 ! REMARKS: remark:
37 ! NO-REMARKS-NOT: remark:
40 ! With plain -Rpass, -Rpass-missed or -Rpass-analysis, we expect remarks related to 2 opportunities (loop vectorisation / loop delete and load hoisting).
41 ! Once we start filtering, this is reduced to 1 one of the loop passes.
43 ! PASS-REGEX-LOOP-ONLY-NOT: optimization-remark.f90:77:7: remark: hoisting load [-Rpass=licm]
44 ! PASS-REGEX-LOOP-ONLY: optimization-remark.f90:79:5: remark: Loop deleted because it is invariant [-Rpass=loop-delete]
46 ! MISSED-REGEX-LOOP-ONLY-NOT: optimization-remark.f90:77:7: remark: failed to hoist load with loop-invariant address because load is conditionally executed [-Rpass-missed=licm]
47 ! MISSED-REGEX-LOOP-ONLY: optimization-remark.f90:72:4: remark: loop not vectorized [-Rpass-missed=loop-vectorize]
50 ! ANALYSIS-REGEX-LOOP-ONLY: optimization-remark.f90:74:7: remark: loop not vectorized: unsafe dependent memory operations in loop
51 ! ANALYSIS-REGEX-LOOP-ONLY-NOT: remark: {{.*}}: IR instruction count changed from {{[0-9]+}} to {{[0-9]+}}; Delta: {{-?[0-9]+}} [-Rpass-analysis=size-info]
53 ! PASS: optimization-remark.f90:79:5: remark: Loop deleted because it is invariant [-Rpass=loop-delete]
55 ! MISSED: optimization-remark.f90:73:7: remark: failed to hoist load with loop-invariant address
56 ! MISSED: optimization-remark.f90:72:4: remark: loop not vectorized [-Rpass-missed=loop-vectorize]
57 ! MISSED-NOT: optimization-remark.f90:75:7: remark: loop not vectorized: unsafe dependent memory operations in loop. Use #pragma clang loop distribute(enable) to allow loop distribution to attempt to isolate the offending operations into a separate loop
58 ! MISSED-NOT: Unknown data dependence. Memory location is the same as accessed at optimization-remark.f90:78:7 [-Rpass-analysis=loop-vectorize]
60 ! ANALYSIS: optimization-remark.f90:74:7: remark: loop not vectorized: unsafe dependent memory operations in loop.
61 ! ANALYSIS: remark: {{.*}} instructions in function [-Rpass-analysis=asm-printer]
63 subroutine swap_real(a1, a2)
64 implicit none
66 real, dimension(1:2) :: aR1
67 integer :: i, n
68 real, intent(inout) :: a1(:), a2(:)
69 real :: a
71 ! Swap
72 do i = 1, min(size(a1), size(a2))
73 a = a1(i)
74 a1(i) = a2(i)
75 a2(i) = a
76 end do
78 ! Do a random loop to generate a successful loop-delete pass
79 do n = 1,2
80 aR1(n) = n * 1.34
81 end do
83 end subroutine swap_real