Skip to content

[stdlib_linalg] Issue with maxval(abs(B-eye(k)) where B is a complex matrix. #920

Closed
@loiseaujc

Description

@loiseaujc

Description

I have a surprising issue when combining fortran intrinsic functions maxval and abs with some functions from stdlib.
Consider the code below.

program main
  ! > Import stdlib_linalg stuff.
  use stdlib_linalg_constants, only: sp, ilp
  use stdlib_linalg, only: eye, qr
  implicit none

  ! > Local variables.
  integer(ilp), parameter :: k = 256
  complex(sp) :: A(1:k, 1:k), B(1:k, 1:k), C(1:k, 1:k)
  complex(sp) :: Q(1:k, 1:k), R(1:k, 1:k)
  real(sp) :: alpha, beta
  integer(ilp) :: i, j

  ! > Initialize A.
  A = 0.0_sp
  do j = 1, k
    do i = 1, k
      call random_number(alpha); call random_number(beta)
      A(i, j) = cmplx(alpha, beta, kind=sp)
    enddo
  enddo

  ! > Perform QR decomposition.
  call qr(A, Q, R)

  ! > Gram matrix.
  B = matmul( transpose(conjg(Q)), Q)

  ! > Difference matrix.
  C = B - eye(k)

  write(*, *) "maxval(abs(B - eye(k))) = ", maxval(abs(B-eye(k)))
  write(*, *) "maxval(abs(C)) = ", maxval(abs(C))

end program main

This is an extremely simplified version of what we're doing in a library we're working on where the call to qr followed by B = matmul(transpose(conjg(Q)), Q) basically emulates a complicated function that should return an orthonormal set of vectors. In our unit tests, we then simply use maxval(abs(B - eye(k))) which should be of the order of the machine precision to ensure that B is indeed the Gram matrix of an orthonormal set of vectors.

When compiling this code with fpm run --compiler "gfortran", here is the output

 maxval(abs(B - eye(k))) =    1.0000000000000000     
 maxval(abs(C)) =    1.31130253E-06

While the second print statement is correct, the first one is not.
For comparison, if I compile with fpm run --compiler "ifx", I get the expected output

 maxval(abs(B - eye(k))) =  9.536743164062500E-007
 maxval(abs(C)) =  9.5367432E-07

I'm running with gfortran 13.3 btw. To me, the error comes from gfortran (possible type conversion) rather than stdlib but I just wanted to raise the issue here to see if anyone can reproduce before reporting this possible gfortran bug.

Expected Behaviour

The two statements maxval(abs(B - eye(k))) and maxval(abs(C)) should return the same value.

Version of stdlib

latest

Platform and Architecture

Ubuntu 22.04, Linux ,gfortran 13.3

Additional Information

No response

Metadata

Metadata

Assignees

No one assigned

    Labels

    bugSomething isn't working

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions