Skip to content

Bug in the complex least-squares solver #823

Closed
@loiseaujc

Description

@loiseaujc

Description

Consider the following code

program main
  use iso_fortran_env, only: output_unit
  use stdlib_kinds, only: dp
  use stdlib_linalg, only: solve_lstsq
  implicit none

  ! Dimension of the problem.
  integer, parameter :: m = 100, n = m-1
  integer :: k
  complex(dp) :: A(m, n), b(m), x_true(n), x_lstsq(n)

  do k = 1, n
      ! Zero-out data.
      A = 0.0_dp ; b = 0.0_dp ; x_true = 0.0_dp ; x_lstsq = 0.0_dp

      ! Generate a random least-squares problem of size (k+1, k).
      call random_number(A(:k+1, :k)%re) ; call random_number(A(:k+1, :k)%im)
      call random_number(x_true(:k)%re) ; call random_number(x_true(:k)%im)
      b(:k+1) = matmul(A(:k+1, :k), x_true(:k))

      ! Solve the lstsq problem.
      call solve_lstsq(A(:k+1, :k), b(:k+1), x_lstsq(:k))

      ! Check correctness of the solution.
      write(output_unit, *) "Iteration k", k, norm2(abs(x_true - x_lstsq))
  end do

end program main

Although it looks quite contrived, it is adapted from a naïve implementation of a gmres solver where A actually is upper Hessenberg. It thus corresponds to the increasingly larger least-squares problem that needs to be solved at each iteration of the gmres solver. In this MWE, A is generated as a random matrix just to make sure the error I'll report does not depends on the structure of the matrix.

Initially, everything runs just fine. However, the code crashes for k equal 39 with the following error:

Program received signal SIGSEGV: Segmentation fault - invalid memory reference.

Backtrace for this error:
#0  0x7f147f8eb51f in ???
#1  0x7f147f94b838 in ???
#2  0x7f147f94e452 in ???
#3  0x559663cefe05 in __stdlib_linalg_MOD_stdlib_linalg_z_solve_lstsq_one
	at build/dependencies/stdlib/src/stdlib_linalg_least_squares.f90:1142
#4  0x559663cc6b47 in MAIN__
	at app/main.f90:115
#5  0x559663ccd799 in main
	at app/main.f90:3
Segmentation fault (core dumped)
<ERROR> Execution for object " MWE_stdlib_lstsq " returned exit code  139
<ERROR> *cmd_run*:stopping due to failed executions
STOP 139

Not that the error reported actually randomly switches between double free or corruption (out) (with STOP 134), SIGSEGV (with STOP 139), munmap_chunk(): invalid pointer (with STOP 134), or free(): invalide size (with STOP 134). If single precision is used instead of double precision, the code crashes at iteration k = 39 instead.

Expected Behaviour

The code should runs smoothly. Note that if real variables instead of complex ones are being used, no problem is encountered.

Version of stdlib

0.6.1

Platform and Architecture

Linux with Ubuntu 22.04

Additional Information

The code is generated with fpm and the latest stdlib version is fetched directly by fpm. The code is compiled with gfortran 13.2.0 installed with conda.

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