4
4
module test_linalg_least_squares
5
5
use testdrive, only: error_type, check, new_unittest, unittest_type
6
6
use stdlib_linalg_constants
7
- use stdlib_linalg, only: lstsq
7
+ use stdlib_linalg, only: lstsq,solve_lstsq
8
8
use stdlib_linalg_state, only: linalg_state_type
9
9
10
10
implicit none (type,external)
@@ -20,6 +20,8 @@ module test_linalg_least_squares
20
20
type(unittest_type), allocatable, intent(out) :: tests(:)
21
21
22
22
allocate(tests(0))
23
+
24
+ tests = [tests,new_unittest("issue_823",test_issue_823)]
23
25
24
26
#:for rk,rt,ri in REAL_KINDS_TYPES
25
27
#:if rk!="xdp"
@@ -100,6 +102,46 @@ module test_linalg_least_squares
100
102
101
103
#:endif
102
104
#:endfor
105
+
106
+ ! Test issue #823
107
+ subroutine test_issue_823(error)
108
+ type(error_type), allocatable, intent(out) :: error
109
+
110
+ ! Dimension of the problem.
111
+ integer(ilp), parameter :: n = 42
112
+ ! Data for the least-squares problem.
113
+ complex(dp) :: A(n+1, n), b(n+1), x_true(n), x_lstsq(n)
114
+ ! Internal variables.
115
+ real(dp), allocatable :: tmp(:, :, :), tmp_vec(:, :)
116
+ ! Error handler
117
+ type(linalg_state_type) :: state
118
+
119
+ ! Zero-out data.
120
+ A = 0.0_dp
121
+ b = 0.0_dp
122
+ x_lstsq = 0.0_dp
123
+ allocate(tmp(n+1, n, 2), tmp_vec(n, 2), source=0.0_dp)
124
+
125
+ ! Generate a random complex least-squares problem of size (n+1, n).
126
+ call random_number(tmp)
127
+ call random_number(tmp_vec)
128
+
129
+ A = cmplx(tmp(:, :, 1), tmp(:, :, 2), kind=dp)
130
+ x_true = cmplx(tmp_vec(:, 1), tmp_vec(:, 2), kind=dp)
131
+ b = matmul(A, x_true)
132
+
133
+ ! Solve the lstsq problem.
134
+ call solve_lstsq(A, b, x_lstsq, err=state)
135
+
136
+ ! Check that no segfault occurred
137
+ call check(error,state%ok(),'issue 823 returned '//state%print())
138
+ if (allocated(error)) return
139
+
140
+ ! Check that least squares are verified
141
+ call check(error,all(abs(x_true-x_lstsq)<sqrt(epsilon(0.0_dp))),'issue 823 results')
142
+ if (allocated(error)) return
143
+
144
+ end subroutine test_issue_823
103
145
104
146
end module test_linalg_least_squares
105
147
0 commit comments