@@ -29,6 +29,9 @@ module stdlib_linalg
2929 public :: inv
3030 public :: invert
3131 public :: operator(.inv.)
32+ public :: pinv
33+ public :: pseudoinvert
34+ public :: operator(.pinv.)
3235 public :: lstsq
3336 public :: lstsq_space
3437 public :: norm
@@ -846,6 +849,131 @@ module stdlib_linalg
846849 end interface operator(.inv.)
847850
848851
852+ ! Moore-Penrose Pseudo-Inverse: Function interface
853+ interface pinv
854+ !! version: experimental
855+ !!
856+ !! Pseudo-inverse of a matrix
857+ !! ([Specification](../page/specs/stdlib_linalg.html#pinv-moore-penrose-pseudo-inverse-of-a-matrix))
858+ !!
859+ !!### Summary
860+ !! This interface provides methods for computing the Moore-Penrose pseudo-inverse of a matrix.
861+ !! The pseudo-inverse \( A^{+} \) is a generalization of the matrix inverse, computed for square, singular,
862+ !! or rectangular matrices. It is defined such that it satisfies the conditions:
863+ !! - \( A \cdot A^{+} \cdot A = A \)
864+ !! - \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
865+ !! - \( (A \cdot A^{+})^T = A \cdot A^{+} \)
866+ !! - \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
867+ !!
868+ !!### Description
869+ !!
870+ !! This function interface provides methods that return the Moore-Penrose pseudo-inverse of a matrix.
871+ !! Supported data types include `real` and `complex`.
872+ !! The pseudo-inverse \( A^{+} \) is returned as a function result. The computation is based on the
873+ !! singular value decomposition (SVD). An optional relative tolerance `rtol` is provided to control the
874+ !! inclusion of singular values during inversion. Singular values below \( \text{rtol} \cdot \sigma_{\max} \)
875+ !! are treated as zero, where \( \sigma_{\max} \) is the largest singular value. If `rtol` is not provided,
876+ !! a default threshold is applied.
877+ !!
878+ !! Exceptions are raised in case of computational errors or invalid input, and trigger an `error stop`
879+ !! if the state flag `err` is not provided.
880+ !!
881+ !!@note The provided functions are intended for both rectangular and square matrices.
882+ !!
883+ #:for rk,rt,ri in RC_KINDS_TYPES
884+ module function stdlib_linalg_pseudoinverse_${ri}$(a,rtol,err) result(pinva)
885+ !> Input matrix a[m,n]
886+ ${rt}$, intent(in), target :: a(:,:)
887+ !> [optional] Relative tolerance for singular value cutoff
888+ real(${rk}$), optional, intent(in) :: rtol
889+ !> [optional] State return flag. On error if not requested, the code will stop
890+ type(linalg_state_type), optional, intent(out) :: err
891+ !> Output matrix pseudo-inverse [n,m]
892+ ${rt}$ :: pinva(size(a,2,kind=ilp),size(a,1,kind=ilp))
893+ end function stdlib_linalg_pseudoinverse_${ri}$
894+ #:endfor
895+ end interface pinv
896+
897+ ! Moore-Penrose Pseudo-Inverse: Subroutine interface
898+ interface pseudoinvert
899+ !! version: experimental
900+ !!
901+ !! Computation of the Moore-Penrose pseudo-inverse
902+ !! ([Specification](../page/specs/stdlib_linalg.html#pseudoinvert-moore-penrose-pseudo-inverse-of-a-matrix))
903+ !!
904+ !!### Summary
905+ !! This interface provides methods for computing the Moore-Penrose pseudo-inverse of a rectangular
906+ !! or square `real` or `complex` matrix.
907+ !! The pseudo-inverse \( A^{+} \) generalizes the matrix inverse and satisfies the properties:
908+ !! - \( A \cdot A^{+} \cdot A = A \)
909+ !! - \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
910+ !! - \( (A \cdot A^{+})^T = A \cdot A^{+} \)
911+ !! - \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
912+ !!
913+ !!### Description
914+ !!
915+ !! This subroutine interface provides a way to compute the Moore-Penrose pseudo-inverse of a matrix.
916+ !! Supported data types include `real` and `complex`.
917+ !! Users must provide two matrices: the input matrix `a` [m,n] and the output pseudo-inverse `pinva` [n,m].
918+ !! The input matrix `a` is used to compute the pseudo-inverse and is not modified. The computed
919+ !! pseudo-inverse is stored in `pinva`. The computation is based on the singular value decomposition (SVD).
920+ !!
921+ !! An optional relative tolerance `rtol` is used to control the inclusion of singular values in the
922+ !! computation. Singular values below \( \text{rtol} \cdot \sigma_{\max} \) are treated as zero,
923+ !! where \( \sigma_{\max} \) is the largest singular value. If `rtol` is not provided, a default
924+ !! threshold is applied.
925+ !!
926+ !! Exceptions are raised in case of computational errors or invalid input, and trigger an `error stop`
927+ !! if the state flag `err` is not provided.
928+ !!
929+ !!@note The provided subroutines are intended for both rectangular and square matrices.
930+ !!
931+ #:for rk,rt,ri in RC_KINDS_TYPES
932+ module subroutine stdlib_linalg_pseudoinvert_${ri}$(a,pinva,rtol,err)
933+ !> Input matrix a[m,n]
934+ ${rt}$, intent(inout) :: a(:,:)
935+ !> Output pseudo-inverse matrix [n,m]
936+ ${rt}$, intent(out) :: pinva(:,:)
937+ !> [optional] Relative tolerance for singular value cutoff
938+ real(${rk}$), optional, intent(in) :: rtol
939+ !> [optional] State return flag. On error if not requested, the code will stop
940+ type(linalg_state_type), optional, intent(out) :: err
941+ end subroutine stdlib_linalg_pseudoinvert_${ri}$
942+ #:endfor
943+ end interface pseudoinvert
944+
945+ ! Moore-Penrose Pseudo-Inverse: Operator interface
946+ interface operator(.pinv.)
947+ !! version: experimental
948+ !!
949+ !! Pseudo-inverse operator of a matrix
950+ !! ([Specification](../page/specs/stdlib_linalg.html#pinv-moore-penrose-pseudo-inverse-operator))
951+ !!
952+ !!### Summary
953+ !! Operator interface for computing the Moore-Penrose pseudo-inverse of a `real` or `complex` matrix.
954+ !!
955+ !!### Description
956+ !!
957+ !! This operator interface provides a convenient way to compute the Moore-Penrose pseudo-inverse
958+ !! of a matrix. Supported data types include `real` and `complex`. The pseudo-inverse \( A^{+} \)
959+ !! is computed using singular value decomposition (SVD), with singular values below an internal
960+ !! threshold treated as zero.
961+ !!
962+ !! For computational errors or invalid input, the function may return a matrix filled with NaNs.
963+ !!
964+ !!@note The provided functions are intended for both rectangular and square matrices.
965+ !!
966+ #:for rk,rt,ri in RC_KINDS_TYPES
967+ module function stdlib_linalg_pinv_${ri}$_operator(a) result(pinva)
968+ !> Input matrix a[m,n]
969+ ${rt}$, intent(in), target :: a(:,:)
970+ !> Result pseudo-inverse matrix
971+ ${rt}$ :: pinva(size(a,2,kind=ilp),size(a,1,kind=ilp))
972+ end function stdlib_linalg_pinv_${ri}$_operator
973+ #:endfor
974+ end interface operator(.pinv.)
975+
976+
849977 ! Eigendecomposition of a square matrix: eigenvalues, and optionally eigenvectors
850978 interface eig
851979 !! version: experimental
0 commit comments