You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
Copy file name to clipboardExpand all lines: doc/specs/stdlib_linalg.md
+126-9Lines changed: 126 additions & 9 deletions
Original file line number
Diff line number
Diff line change
@@ -625,9 +625,7 @@ Expert interface:
625
625
`x = `[[stdlib_linalg(module):solve(interface)]]`(a, b [, overwrite_a], err)`
626
626
627
627
### Arguments
628
-
629
-
Two
630
-
628
+
631
629
`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.
632
630
633
631
`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 =
664
662
665
663
Result vector or array `x` returns the exact solution to within numerical precision, provided that the matrix is not ill-conditioned.
666
664
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.
667
666
The solver is based on LAPACK's `*GESV` backends.
668
667
669
668
### Syntax
@@ -678,8 +677,6 @@ Expert (`Pure`) interface:
678
677
679
678
### Arguments
680
679
681
-
Two
682
-
683
680
`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.
684
681
685
682
`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
690
687
691
688
`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.
692
689
693
-
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
694
-
695
690
### Return value
696
691
697
692
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`.
703
698
### Example
704
699
705
700
```fortran
706
-
{!example/linalg/example_solve1.f90!}
701
+
{!example/linalg/example_solve3.f90!}
702
+
```
707
703
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.
`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!}
709
746
```
710
747
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.
`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)]] .
`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
+
711
828
## `det` - Computes the determinant of a square matrix
0 commit comments