Skip to content

Commit da16d0f

Browse files
authored
Merge branch 'master' into linalg_solve
2 parents 7aab844 + 33559f5 commit da16d0f

File tree

9 files changed

+806
-14
lines changed

9 files changed

+806
-14
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 126 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -625,9 +625,7 @@ Expert interface:
625625
`x = ` [[stdlib_linalg(module):solve(interface)]] `(a, b [, overwrite_a], err)`
626626

627627
### Arguments
628-
629-
Two
630-
628+
631629
`a`: Shall be a rank-2 `real` or `complex` square array containing the coefficient matrix. It is normally an `intent(in)` argument. If `overwrite_a=.true.`, it is an `intent(inout)` argument and is destroyed by the call.
632630

633631
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing the right-hand-side vector(s). It is an `intent(in)` argument.
@@ -664,6 +662,7 @@ This subroutine computes the solution to a linear matrix equation \( A \cdot x =
664662

665663
Result vector or array `x` returns the exact solution to within numerical precision, provided that the matrix is not ill-conditioned.
666664
An error is returned if the matrix is rank-deficient or singular to working precision.
665+
If all optional arrays are provided by the user, no internal allocations take place.
667666
The solver is based on LAPACK's `*GESV` backends.
668667

669668
### Syntax
@@ -678,8 +677,6 @@ Expert (`Pure`) interface:
678677

679678
### Arguments
680679

681-
Two
682-
683680
`a`: Shall be a rank-2 `real` or `complex` square array containing the coefficient matrix. It is normally an `intent(in)` argument. If `overwrite_a=.true.`, it is an `intent(inout)` argument and is destroyed by the call.
684681

685682
`b`: Shall be a rank-1 or rank-2 array of the same kind as `a`, containing the right-hand-side vector(s). It is an `intent(in)` argument.
@@ -690,8 +687,6 @@ Two
690687

691688
`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.
692689

693-
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
694-
695690
### Return value
696691

697692
For a full-rank matrix, returns an array value that represents the solution to the linear system of equations.
@@ -703,11 +698,133 @@ If `err` is not present, exceptions trigger an `error stop`.
703698
### Example
704699

705700
```fortran
706-
{!example/linalg/example_solve1.f90!}
701+
{!example/linalg/example_solve3.f90!}
702+
```
707703

708-
{!example/linalg/example_solve2.f90!}
704+
## `lstsq` - Computes the least squares solution to a linear matrix equation.
705+
706+
### Status
707+
708+
Experimental
709+
710+
### Description
711+
712+
This function computes the least-squares solution to a linear matrix equation \( A \cdot x = b \).
713+
714+
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.
715+
716+
### Syntax
717+
718+
`x = ` [[stdlib_linalg(module):lstsq(interface)]] `(a, b, [, cond, overwrite_a, rank, err])`
719+
720+
### Arguments
721+
722+
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
723+
724+
`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.
725+
726+
`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.
727+
728+
`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.
729+
730+
`rank` (optional): Shall be an `integer` scalar value, that contains the rank of input matrix `A`. This is an `intent(out)` argument.
731+
732+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
733+
734+
### Return value
735+
736+
Returns an array value of the same kind and rank as `b`, containing the solution(s) to the least squares system.
737+
738+
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
739+
Raises `LINALG_VALUE_ERROR` if the matrix and right-hand-side vector have invalid/incompatible sizes.
740+
Exceptions trigger an `error stop`.
741+
742+
### Example
743+
744+
```fortran
745+
{!example/linalg/example_lstsq1.f90!}
709746
```
710747

748+
## `solve_lstsq` - Compute the least squares solution to a linear matrix equation (subroutine interface).
749+
750+
### Status
751+
752+
Experimental
753+
754+
### Description
755+
756+
This subroutine computes the least-squares solution to a linear matrix equation \( A \cdot x = b \).
757+
758+
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.
759+
760+
### Syntax
761+
762+
`call ` [[stdlib_linalg(module):solve_lstsq(interface)]] `(a, b, x, [, real_storage, int_storage, [cmpl_storage, ] cond, singvals, overwrite_a, rank, err])`
763+
764+
### Arguments
765+
766+
`a`: Shall be a rank-2 `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
767+
768+
`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.
769+
770+
`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.
771+
772+
`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.
773+
774+
`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.
775+
776+
`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.
777+
778+
`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.
779+
780+
`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.
781+
782+
`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.
783+
784+
`rank` (optional): Shall be an `integer` scalar value, that contains the rank of input matrix `A`. This is an `intent(out)` argument.
785+
786+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
787+
788+
### Return value
789+
790+
Returns an array value that represents the solution to the least squares system.
791+
792+
Raises `LINALG_ERROR` if the underlying Singular Value Decomposition process did not converge.
793+
Raises `LINALG_VALUE_ERROR` if the matrix and right-hand-side vector have invalid/incompatible sizes.
794+
Exceptions trigger an `error stop`.
795+
796+
### Example
797+
798+
```fortran
799+
{!example/linalg/example_lstsq2.f90!}
800+
```
801+
802+
## `lstsq_space` - Compute internal working space requirements for the least squares solver.
803+
804+
### Status
805+
806+
Experimental
807+
808+
### Description
809+
810+
This subroutine computes the internal working space requirements for the least-squares solver, [[stdlib_linalg(module):solve_lstsq(interface)]] .
811+
812+
### Syntax
813+
814+
`call ` [[stdlib_linalg(module):lstsq_space(interface)]] `(a, b, lrwork, liwork [, lcwork])`
815+
816+
### Arguments
817+
818+
`a`: Shall be a rank-2 `real` or `complex` array containing the linear system coefficient matrix. It is an `intent(in)` argument.
819+
820+
`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.
821+
822+
`lrwork`: Shall be an `integer` scalar, that returns the minimum array size required for the `real` working storage to this system.
823+
824+
`liwork`: Shall be an `integer` scalar, that returns the minimum array size required for the `integer` working storage to this system.
825+
826+
`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.
827+
711828
## `det` - Computes the determinant of a square matrix
712829

713830
### Status

example/linalg/CMakeLists.txt

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,8 @@ ADD_EXAMPLE(state1)
1818
ADD_EXAMPLE(state2)
1919
ADD_EXAMPLE(blas_gemv)
2020
ADD_EXAMPLE(lapack_getrf)
21+
ADD_EXAMPLE(lstsq1)
22+
ADD_EXAMPLE(lstsq2)
2123
ADD_EXAMPLE(solve1)
2224
ADD_EXAMPLE(solve2)
2325
ADD_EXAMPLE(solve3)

example/linalg/example_lstsq1.f90

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
! Least-squares solver: functional interface
2+
program example_lstsq1
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: lstsq
5+
implicit none
6+
7+
integer, allocatable :: x(:),y(:)
8+
real(dp), allocatable :: A(:,:),b(:),coef(:)
9+
10+
! Data set
11+
x = [1, 2, 2]
12+
y = [5, 13, 25]
13+
14+
! Fit three points using a parabola, least squares method
15+
! A = [1 x x**2]
16+
A = reshape([[1,1,1],x,x**2],[3,3])
17+
b = y
18+
19+
! Get coefficients of y = coef(1) + x*coef(2) + x^2*coef(3)
20+
coef = lstsq(A,b)
21+
22+
print *, 'parabola: ',coef
23+
! parabola: -0.42857142857141695 1.1428571428571503 4.2857142857142811
24+
25+
26+
end program example_lstsq1

example/linalg/example_lstsq2.f90

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,40 @@
1+
! Demonstrate expert subroutine interface with pre-allocated arrays
2+
program example_lstsq2
3+
use stdlib_linalg_constants, only: dp,ilp
4+
use stdlib_linalg, only: solve_lstsq, lstsq_space, linalg_state_type
5+
implicit none
6+
7+
integer, allocatable :: x(:),y(:)
8+
real(dp), allocatable :: A(:,:),b(:),coef(:),real_space(:),singvals(:)
9+
integer(ilp), allocatable :: int_space(:)
10+
integer(ilp) :: lrwork,liwork,arank
11+
12+
! Data set
13+
x = [1, 2, 2]
14+
y = [5, 13, 25]
15+
16+
! Fit three points using a parabola, least squares method
17+
! A = [1 x x**2]
18+
A = reshape([[1,1,1],x,x**2],[3,3])
19+
b = y
20+
21+
! Get storage sizes for the arrays and pre-allocate data
22+
call lstsq_space(A,b,lrwork,liwork)
23+
allocate(coef(size(x)),real_space(lrwork),int_space(liwork),singvals(minval(shape(A))))
24+
25+
! Solve coefficients of y = coef(1) + x*coef(2) + x^2*coef(3)
26+
! with no internal allocations
27+
call solve_lstsq(A,b,x=coef, &
28+
real_storage=real_space, &
29+
int_storage=int_space, &
30+
singvals=singvals, &
31+
overwrite_a=.true., &
32+
rank=arank)
33+
34+
print *, 'parabola: ',coef
35+
! parabola: -0.42857142857141695 1.1428571428571503 4.2857142857142811
36+
print *, 'rank: ',arank
37+
! rank: 2
38+
39+
40+
end program example_lstsq2

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ set(fppFiles
2121
stdlib_kinds.fypp
2222
stdlib_linalg.fypp
2323
stdlib_linalg_diag.fypp
24+
stdlib_linalg_least_squares.fypp
2425
stdlib_linalg_outer_product.fypp
2526
stdlib_linalg_kronecker.fypp
2627
stdlib_linalg_cross_product.fypp

0 commit comments

Comments
 (0)