flang
                                
                                
                                
                                    flang copied to clipboard
                            
                            
                            
                        -Mbounds reports false positive for array slices passed to DOT_PRODUCT intrinsic
This is a bug that affects all flang-based compilers: classic flang 7.0.1, Huawei  Bisheng flang 1.3.3, NVIDIA nvfortran 22.3, and AOCC 3.2.0 flang. They raise a false positive error of out-bound subscripts when invoked with the -Mbounds flag.
Here is a minimal working example. The latest version of the code is available at my GitHub repo dedicated to testing Fortran compilers.
! test_solve.f90
module solve_mod
implicit none
private
public :: solve
contains
function solve(A, b) result(x)  ! A naive solver for upper-triangle linear systems
implicit none
real, intent(in) :: A(:, :), b(:)
real :: x(size(A, 2))
integer :: i, n
n = size(b) 
do i = n, 1, -1
    x(i) = (b(i) - inprod(A(i, i + 1:n), x(i + 1:n))) / A(i, i)
    !x(i) = (b(i) - dot_product(A(i, i + 1:n), x(i + 1:n))) / A(i, i)  ! No problem will arise
end do
end function solve
function inprod(x, y) result(z)
real, intent(in) :: x(:), y(:)
real :: z
z = dot_product(x, y)
end function inprod
end module solve_mod
program test_solve
use, non_intrinsic :: solve_mod, only : solve
implicit none
real :: A(1, 1), b(1)
A = 1.0
b = 1.0
write (*, *) solve(A, b)
end program test_solve
The error message looks like the following.
$ flang -Mbounds test_solve.f90 && ./a.out
0: Subscript out of range for array x (test_solve.f90: 19)
    subscript=2, lower bound=1, upper bound=1, dimension=1
Thank you for having a look at it.
To be clear, when i = n = 1, the Fortran standard says that A(i, i + 1:n) and x(i + 1:n) are valid and they should be empty arrays. So this is a false positive.
Note that the false positive occurs only if we invoke the compilers with -Mbounds.
For your reference, see what I reported to NVIDIA before in “Bug of nvfortran 22.2-0: array subscript triplet handled wrongly”, in case they are related. [Update 20230526: They turn out to be different bugs.]
@mleair Do you have any information on the NVIDIA bug? Is that fix applicable to open-source Flang?
@d-parks
The fix checks for an empty section under the A_SUBSCR case in collapse_assignment() in transfrm.c. The check looks like this:
case A_SUBSCR:
if (!contiguous_section(rhs) || is_empty_section(rhs))
      return 0;
Originally, the check looked like this:
case A_SUBSCR:
if (!contiguous_section(rhs))
      return 0;
The is_empty_section() function checks for a zero size array section.
-Mark
@mleair Thanks a lot Mark! Would it be possible for you guys to upstream that fix? 😄
@bryanpkc Sorry, I am too busy right now to implement, test, and upstream the fix.
@bryanpkc I am available to answer any additional questions, though.
FYI, the problem remains in flang 15.0.3.
This bug is the same as the following one in nvfortran 22.3, which has been fixed now by 23.5.
https://forums.developer.nvidia.com/t/bug-in-nvfortran-22-3-false-positive-of-out-bound-subscripts/209936
N.B.: It is DIFFERENT from the following one, which was mentioned earlier by me in this thread. nvfortran 22.5 fixed the following one, but did not fix the one under discussion.
https://forums.developer.nvidia.com/t/bug-of-nvfortran-22-2-0-array-subscript-triplet-handled-wrongly/208395
hello @mleair, would it be possible to post the is_empty_section function code ? I would like to try to upstream a patch
I looked at this problem briefly. I am not sure that Mark's proposed solution is relevant. The crux of the problem is that Classic Flang lacks proper bounds checking for array sections; a triple expression is handled incorrectly as if it is just a single subscript. An extension of the complicated logic in the A_SUBSCR case in lower_ast() is needed.