@@ -812,50 +812,131 @@ module stdlib_linalg
812
812
end interface operator(.inv.)
813
813
814
814
815
- ! Moose -Penrose Pseudo-Inverse: Function interface
815
+ ! Moore -Penrose Pseudo-Inverse: Function interface
816
816
interface pinv
817
+ !! version: experimental
818
+ !!
819
+ !! Pseudo-inverse of a matrix
820
+ !! ([Specification](../page/specs/stdlib_linalg.html#pinv-pseudo-inverse-of-a-matrix))
821
+ !!
822
+ !!### Summary
823
+ !! This interface provides methods for computing the Moore-Penrose pseudo-inverse of a matrix.
824
+ !! The pseudo-inverse \( A^{+} \) is a generalization of the matrix inverse, computed for square, singular,
825
+ !! or rectangular matrices. It is defined such that it satisfies the conditions:
826
+ !! - \( A \cdot A^{+} \cdot A = A \)
827
+ !! - \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
828
+ !! - \( (A \cdot A^{+})^T = A \cdot A^{+} \)
829
+ !! - \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
830
+ !!
831
+ !!### Description
832
+ !!
833
+ !! This function interface provides methods that return the Moore-Penrose pseudo-inverse of a matrix.
834
+ !! Supported data types include `real` and `complex`.
835
+ !! The pseudo-inverse \( A^{+} \) is returned as a function result. The computation is based on the
836
+ !! singular value decomposition (SVD). An optional relative tolerance `rtol` is provided to control the
837
+ !! inclusion of singular values during inversion. Singular values below \( \text{rtol} \cdot \sigma_{\max} \)
838
+ !! are treated as zero, where \( \sigma_{\max} \) is the largest singular value. If `rtol` is not provided,
839
+ !! a default threshold is applied.
840
+ !!
841
+ !! Exceptions are raised in case of computational errors or invalid input, and trigger an `error stop`
842
+ !! if the state flag `err` is not provided.
843
+ !!
844
+ !!@note The provided functions are intended for both rectangular and square matrices.
845
+ !!
817
846
#:for rk,rt,ri in RC_KINDS_TYPES
818
847
module function stdlib_linalg_pseudoinverse_${ri}$(a,rtol,err) result(pinva)
819
848
!> Input matrix a[m,n]
820
849
${rt}$, intent(in), target :: a(:,:)
821
- !> [optional] ....
850
+ !> [optional] Relative tolerance for singular value cutoff
822
851
real(${rk}$), optional, intent(in) :: rtol
823
- !> [optional] state return flag. On error if not requested, the code will stop
852
+ !> [optional] State return flag. On error if not requested, the code will stop
824
853
type(linalg_state_type), optional, intent(out) :: err
825
- !> Matrix pseudo-inverse
854
+ !> Output matrix pseudo-inverse [n,m]
826
855
${rt}$ :: pinva(size(a,2,kind=ilp),size(a,1,kind=ilp))
827
856
end function stdlib_linalg_pseudoinverse_${ri}$
828
857
#:endfor
829
858
end interface pinv
830
859
831
- ! Matrix Inverse: Subroutine interface - in-place inversion
860
+ ! Moore-Penrose Pseudo- Inverse: Subroutine interface
832
861
interface pseudoinvert
862
+ !! version: experimental
863
+ !!
864
+ !! Computation of the Moore-Penrose pseudo-inverse
865
+ !! ([Specification](../page/specs/stdlib_linalg.html#pseudoinvert-computation-of-a-matrix-pseudo-inverse))
866
+ !!
867
+ !!### Summary
868
+ !! This interface provides methods for computing the Moore-Penrose pseudo-inverse of a rectangular
869
+ !! or square `real` or `complex` matrix.
870
+ !! The pseudo-inverse \( A^{+} \) generalizes the matrix inverse and satisfies the properties:
871
+ !! - \( A \cdot A^{+} \cdot A = A \)
872
+ !! - \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
873
+ !! - \( (A \cdot A^{+})^T = A \cdot A^{+} \)
874
+ !! - \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
875
+ !!
876
+ !!### Description
877
+ !!
878
+ !! This subroutine interface provides a way to compute the Moore-Penrose pseudo-inverse of a matrix.
879
+ !! Supported data types include `real` and `complex`.
880
+ !! Users must provide two matrices: the input matrix `a` [m,n] and the output pseudo-inverse `pinva` [n,m].
881
+ !! The input matrix `a` is used to compute the pseudo-inverse and is not modified. The computed
882
+ !! pseudo-inverse is stored in `pinva`. The computation is based on the singular value decomposition (SVD).
883
+ !!
884
+ !! An optional relative tolerance `rtol` is used to control the inclusion of singular values in the
885
+ !! computation. Singular values below \( \text{rtol} \cdot \sigma_{\max} \) are treated as zero,
886
+ !! where \( \sigma_{\max} \) is the largest singular value. If `rtol` is not provided, a default
887
+ !! threshold is applied.
888
+ !!
889
+ !! Exceptions are raised in case of computational errors or invalid input, and trigger an `error stop`
890
+ !! if the state flag `err` is not provided.
891
+ !!
892
+ !!@note The provided subroutines are intended for both rectangular and square matrices.
893
+ !!
833
894
#:for rk,rt,ri in RC_KINDS_TYPES
834
895
module subroutine stdlib_linalg_pseudoinvert_${ri}$(a,pinva,rtol,err)
835
896
!> Input matrix a[m,n]
836
- ${rt}$, intent(inout ) :: a(:,:)
837
- !> Output pseudo-inverse matrix
838
- ${rt}$, intent(inout ) :: pinva(:,:)
839
- !> [optional] ....
897
+ ${rt}$, intent(in ) :: a(:,:)
898
+ !> Output pseudo-inverse matrix [n,m]
899
+ ${rt}$, intent(out ) :: pinva(:,:)
900
+ !> [optional] Relative tolerance for singular value cutoff
840
901
real(${rk}$), optional, intent(in) :: rtol
841
- !> [optional] state return flag. On error if not requested, the code will stop
902
+ !> [optional] State return flag. On error if not requested, the code will stop
842
903
type(linalg_state_type), optional, intent(out) :: err
843
- end subroutine
904
+ end subroutine stdlib_linalg_pseudoinvert_${ri}$
844
905
#:endfor
845
906
end interface pseudoinvert
846
907
847
- ! Operator interface
908
+ ! Moore-Penrose Pseudo-Inverse: Operator interface
848
909
interface operator(.pinv.)
849
- #:for rk,rt,ri in RC_KINDS_TYPES
850
- module function stdlib_linalg_pinv_${ri}$_operator(a) result(pinva)
910
+ !! version: experimental
911
+ !!
912
+ !! Pseudo-inverse operator of a matrix
913
+ !! ([Specification](../page/specs/stdlib_linalg.html#pinv-pseudo-inverse-operator-of-a-matrix))
914
+ !!
915
+ !!### Summary
916
+ !! Operator interface for computing the Moore-Penrose pseudo-inverse of a `real` or `complex` matrix.
917
+ !!
918
+ !!### Description
919
+ !!
920
+ !! This operator interface provides a convenient way to compute the Moore-Penrose pseudo-inverse
921
+ !! of a matrix. Supported data types include `real` and `complex`. The pseudo-inverse \( A^{+} \)
922
+ !! is computed using singular value decomposition (SVD), with singular values below an internal
923
+ !! threshold treated as zero.
924
+ !!
925
+ !! For computational errors or invalid input, the function may return a matrix filled with NaNs.
926
+ !!
927
+ !!@note The provided functions are intended for both rectangular and square matrices.
928
+ !!
929
+ #:for rk,rt,ri in RC_KINDS_TYPES
930
+ module function stdlib_linalg_pinv_${ri}$_operator(a) result(pinva)
851
931
!> Input matrix a[m,n]
852
932
${rt}$, intent(in), target :: a(:,:)
853
- !> Result matrix
933
+ !> Result pseudo-inverse matrix
854
934
${rt}$ :: pinva(size(a,2,kind=ilp),size(a,1,kind=ilp))
855
- end function
856
- #:endfor
935
+ end function stdlib_linalg_pinv_${ri}$_operator
936
+ #:endfor
857
937
end interface operator(.pinv.)
858
938
939
+
859
940
! Eigendecomposition of a square matrix: eigenvalues, and optionally eigenvectors
860
941
interface eig
861
942
!! version: experimental
0 commit comments