Skip to content

Commit c55583d

Browse files
committed
document solve_lstsq and lstsq_space
1 parent 18151e6 commit c55583d

File tree

3 files changed

+86
-6
lines changed

3 files changed

+86
-6
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 82 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -620,7 +620,7 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
620620

621621
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
622622

623-
`b`: Shall be a rank-1 array of the same kind as `a`, containing the right-hand-side vector. It is an `intent(in)` argument.
623+
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing one or more right-hand-side vector(s), each in its leading dimension. It is an `intent(in)` argument.
624624

625625
`cond` (optional): Shall be a scalar `real` value cut-off threshold for rank evaluation: `s_i >= cond*maxval(s), i=1:rank`. Shall be a scalar, `intent(in)` argument.
626626

@@ -632,6 +632,60 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
632632

633633
### Return value
634634

635+
Returns an array value of the same kind and rank as `b`, containing the solution(s) to the least squares system.
636+
637+
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
638+
Raises `LINALG_VALUE_ERROR` if the matrix and right-hand-side vector have invalid/incompatible sizes.
639+
Exceptions trigger an `error stop`.
640+
641+
### Example
642+
643+
```fortran
644+
{!example/linalg/example_lstsq1.f90!}
645+
```
646+
647+
## `solve_lstsq` - Compute the least squares solution to a linear matrix equation (subroutine interface).
648+
649+
### Status
650+
651+
Experimental
652+
653+
### Description
654+
655+
This subroutine computes the least-squares solution to a linear matrix equation \( A \cdot x = b \).
656+
657+
Result vector `x` returns the approximate solution that minimizes the 2-norm \( || A \cdot x - b ||_2 \), i.e., it contains the least-squares solution to the problem. Matrix `A` may be full-rank, over-determined, or under-determined. The solver is based on LAPACK's `*GELSD` backends.
658+
659+
### Syntax
660+
661+
`call ` [[stdlib_linalg(module):solve_lstsq(interface)]] `(a, b, x, [, real_storage, int_storage, [cmpl_storage, ] cond, singvals, overwrite_a, rank, err])`
662+
663+
### Arguments
664+
665+
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
666+
667+
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing one or more right-hand-side vector(s), each in its leading dimension. It is an `intent(in)` argument.
668+
669+
`x`: Shall be an array of same kind and rank as `b`, containing the solution(s) to the least squares system. It is an `intent(inout)` argument.
670+
671+
`real_storage` (optional): Shall be a `real` rank-1 array of the same kind `a`, providing working storage for the solver. It minimum size can be determined with a call to [[stdlib_linalg(module):lstsq_space(interface)]]. It is an `intent(inout)` argument.
672+
673+
`int_storage` (optional): Shall be an `integer` rank-1 array, providing working storage for the solver. It minimum size can be determined with a call to [[stdlib_linalg(module):lstsq_space(interface)]]. It is an `intent(inout)` argument.
674+
675+
`cmpl_storage` (optional): For `complex` systems, it shall be a `complex` rank-1 array, providing working storage for the solver. It minimum size can be determined with a call to [[stdlib_linalg(module):lstsq_space(interface)]]. It is an `intent(inout)` argument.
676+
677+
`cond` (optional): Shall be a scalar `real` value cut-off threshold for rank evaluation: `s_i >= cond*maxval(s), i=1:rank`. Shall be a scalar, `intent(in)` argument.
678+
679+
`singvals` (optional): Shall be a `real` rank-1 array of the same kind `a` and size at least `minval(shape(a))`, returning the list of singular values `s(i)>=cond*maxval(s)`, in descending order of magnitude. It is an `intent(out)` argument.
680+
681+
`overwrite_a` (optional): Shall be an input `logical` flag. If `.true.`, input matrix `A` will be used as temporary storage and overwritten. This avoids internal data allocation. This is an `intent(in)` argument.
682+
683+
`rank` (optional): Shall be an `integer` scalar value, that contains the rank of input matrix `A`. This is an `intent(out)` argument.
684+
685+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
686+
687+
### Return value
688+
635689
Returns an array value that represents the solution to the least squares system.
636690

637691
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
@@ -641,9 +695,35 @@ Exceptions trigger an `error stop`.
641695
### Example
642696

643697
```fortran
644-
{!example/linalg/example_lstsq.f90!}
698+
{!example/linalg/example_lstsq2.f90!}
645699
```
646700

701+
## `lstsq_space` - Compute internal working space requirements for the least squares solver.
702+
703+
### Status
704+
705+
Experimental
706+
707+
### Description
708+
709+
This subroutine computes the internal working space requirements for the least-squares solver, [[stdlib_linalg(module):solve_lstsq(interface)]] .
710+
711+
### Syntax
712+
713+
`call ` [[stdlib_linalg(module):lstsq_space(interface)]] `(a, b, lrwork, liwork [, lcwork])`
714+
715+
### Arguments
716+
717+
`a`: Shall be a rank-2 `real` or `complex` array containing the linear system coefficient matrix. It is an `intent(in)` argument.
718+
719+
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing the system's right-hand-side vector(s). It is an `intent(in)` argument.
720+
721+
`lrwork`: Shall be an `integer` scalar, that returns the minimum array size required for the `real` working storage to this system.
722+
723+
`liwork`: Shall be an `integer` scalar, that returns the minimum array size required for the `integer` working storage to this system.
724+
725+
`lcwork` (`complex` `a`, `b`): For a `complex` system, shall be an `integer` scalar, that returns the minimum array size required for the `complex` working storage to this system.
726+
647727
## `det` - Computes the determinant of a square matrix
648728

649729
### Status

src/stdlib_linalg.fypp

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -275,7 +275,7 @@ module stdlib_linalg
275275
!! version: experimental
276276
!!
277277
!! Computes the squares solution to system \( A \cdot x = b \).
278-
!! ([Specification](../page/specs/stdlib_linalg.html))
278+
!! ([Specification](../page/specs/stdlib_linalg.html#solve-lstsq-compute-the-least-squares-solution-to-a-linear-matrix-equation-subroutine-interface))
279279
!!
280280
!!### Summary
281281
!! Subroutine interface for computing least squares, i.e. the 2-norm \( || (b-A \cdot x ||_2 \) minimizing solution.
@@ -329,7 +329,7 @@ module stdlib_linalg
329329
!! version: experimental
330330
!!
331331
!! Computes the integer, real [, complex] working space required by the least-squares solver
332-
!! ([Specification](../page/specs/stdlib_linalg.html))
332+
!! ([Specification](../page/specs/stdlib_linalg.html#lstsq-space-compute-internal-working-space-requirements-for-the-least-squares-solver))
333333
!!
334334
!!### Description
335335
!!
@@ -343,7 +343,7 @@ module stdlib_linalg
343343
#:if rk!="xdp"
344344
pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
345345
!> Input matrix a[m,n]
346-
${rt}$, intent(inout), target :: a(:,:)
346+
${rt}$, intent(in), target :: a(:,:)
347347
!> Right hand side vector or array, b[n] or b[n,nrhs]
348348
${rt}$, intent(in) :: b${nd}$
349349
!> Size of the working space arrays

src/stdlib_linalg_least_squares.fypp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ submodule (stdlib_linalg) stdlib_linalg_least_squares
8484
! Compute the integer, real, [complex] working space requested byu the least squares procedure
8585
pure module subroutine stdlib_linalg_${ri}$_lstsq_space_${ndsuf}$(a,b,lrwork,liwork#{if rt.startswith('c')}#,lcwork#{endif}#)
8686
!> Input matrix a[m,n]
87-
${rt}$, intent(inout), target :: a(:,:)
87+
${rt}$, intent(in), target :: a(:,:)
8888
!> Right hand side vector or array, b[n] or b[n,nrhs]
8989
${rt}$, intent(in) :: b${nd}$
9090
!> Size of the working space arrays

0 commit comments

Comments
 (0)