Skip to content

Commit 36c17fb

Browse files
committed
Working implementation of constrained lstsq.
1 parent 728d221 commit 36c17fb

File tree

1 file changed

+14
-1
lines changed

1 file changed

+14
-1
lines changed

src/stdlib_linalg_least_squares.fypp

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -394,6 +394,19 @@ submodule (stdlib_linalg) stdlib_linalg_least_squares
394394
${rt}$, intent(in), target :: b(:), d(:)
395395
integer(ilp), intent(out) :: lwork
396396
type(linalg_state_type), optional, intent(out) :: err
397+
!> Local variables.
398+
integer(ilp) :: m, n, p, info
399+
${rt}$ :: a_dummy(1, 1), b_dummy(1)
400+
${rt}$ :: c_dummy(1, 1), d_dummy(1)
401+
${rt}$ :: work(1), x(1)
402+
!> Problem dimensions.
403+
m = size(A, 1) ; n = size(A, 2) ; p = size(C, 1)
404+
lwork = -1_ilp
405+
!> Compute constrained lstsq solution.
406+
call gglse(m, n, p, a_dummy, m, c_dummy, p, b_dummy, d_dummy, x, work, lwork, info)
407+
call handle_gglse_info(this, info, m, n, p, err)
408+
!> Optimal workspace size.
409+
lwork = ceiling(real(work(1), kind=${rk}$), kind=ilp)
397410
end subroutine stdlib_linalg_${ri}$_constrained_lstsq_space
398411

399412
module subroutine stdlib_linalg_${ri}$_solve_constrained_lstsq(A, b, C, d, x, storage, overwrite_matrices, err)
@@ -469,7 +482,7 @@ submodule (stdlib_linalg) stdlib_linalg_least_squares
469482
call handle_gglse_info(this, info, ma, na, mc, err0)
470483

471484
!> Deallocate.
472-
deallocate(work)
485+
if (.not. present(storage)) deallocate(work)
473486
endif
474487

475488
if (.not. overwrite_matrices_) then

0 commit comments

Comments
 (0)