Skip to content

Commit 195d4a5

Browse files
authored
linalg: Moore-Penrose pseudo-inverse (pinv) (#899)
2 parents 095219e + 8297763 commit 195d4a5

File tree

9 files changed

+686
-6
lines changed

9 files changed

+686
-6
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 136 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1487,6 +1487,142 @@ If `err` is not present, exceptions trigger an `error stop`.
14871487
{!example/linalg/example_inverse_function.f90!}
14881488
```
14891489

1490+
## `pinv` - Moore-Penrose pseudo-inverse of a matrix
1491+
1492+
### Status
1493+
1494+
Experimental
1495+
1496+
### Description
1497+
1498+
This function computes the Moore-Penrose pseudo-inverse of a `real` or `complex` matrix.
1499+
The pseudo-inverse, \( A^{+} \), generalizes the matrix inverse and satisfies the conditions:
1500+
- \( A \cdot A^{+} \cdot A = A \)
1501+
- \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
1502+
- \( (A \cdot A^{+})^T = A \cdot A^{+} \)
1503+
- \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
1504+
1505+
The computation is based on singular value decomposition (SVD). Singular values below a relative
1506+
tolerance threshold \( \text{rtol} \cdot \sigma_{\max} \), where \( \sigma_{\max} \) is the largest
1507+
singular value, are treated as zero.
1508+
1509+
### Syntax
1510+
1511+
`b =` [[stdlib_linalg(module):pinv(interface)]] `(a, [, rtol, err])`
1512+
1513+
### Arguments
1514+
1515+
`a`: Shall be a rank-2, `real` or `complex` array of shape `[m, n]` containing the coefficient matrix.
1516+
It is an `intent(in)` argument.
1517+
1518+
`rtol` (optional): Shall be a scalar `real` value specifying the relative tolerance for singular value cutoff.
1519+
If `rtol` is not provided, the default relative tolerance is \( \text{rtol} = \text{max}(m, n) \cdot \epsilon \),
1520+
where \( \epsilon \) is the machine precision for the element type of `a`. It is an `intent(in)` argument.
1521+
1522+
`err` (optional): Shall be a `type(linalg_state_type)` value. It is an `intent(out)` argument.
1523+
1524+
### Return value
1525+
1526+
Returns an array value of the same type, kind, and rank as `a` with shape `[n, m]`, that contains the pseudo-inverse matrix \( A^{+} \).
1527+
1528+
Raises `LINALG_ERROR` if the underlying SVD did not converge.
1529+
Raises `LINALG_VALUE_ERROR` if `a` has invalid size.
1530+
If `err` is not present, exceptions trigger an `error stop`.
1531+
1532+
### Example
1533+
1534+
```fortran
1535+
{!example/linalg/example_pseudoinverse.f90!}
1536+
```
1537+
1538+
## `pseudoinvert` - Moore-Penrose pseudo-inverse of a matrix
1539+
1540+
### Status
1541+
1542+
Experimental
1543+
1544+
### Description
1545+
1546+
This subroutine computes the Moore-Penrose pseudo-inverse of a `real` or `complex` matrix.
1547+
The pseudo-inverse \( A^{+} \) is a generalization of the matrix inverse and satisfies the following properties:
1548+
- \( A \cdot A^{+} \cdot A = A \)
1549+
- \( A^{+} \cdot A \cdot A^{+} = A^{+} \)
1550+
- \( (A \cdot A^{+})^T = A \cdot A^{+} \)
1551+
- \( (A^{+} \cdot A)^T = A^{+} \cdot A \)
1552+
1553+
The computation is based on singular value decomposition (SVD). Singular values below a relative
1554+
tolerance threshold \( \text{rtol} \cdot \sigma_{\max} \), where \( \sigma_{\max} \) is the largest
1555+
singular value, are treated as zero.
1556+
1557+
On return, matrix `pinva` `[n, m]` will store the pseudo-inverse of `a` `[m, n]`.
1558+
1559+
### Syntax
1560+
1561+
`call ` [[stdlib_linalg(module):pseudoinvert(interface)]] `(a, pinva [, rtol] [, err])`
1562+
1563+
### Arguments
1564+
1565+
`a`: Shall be a rank-2, `real` or `complex` array containing the coefficient matrix.
1566+
It is an `intent(in)` argument.
1567+
1568+
`pinva`: Shall be a rank-2 array of the same kind as `a`, and size equal to that of `transpose(a)`.
1569+
On output, it contains the Moore-Penrose pseudo-inverse of `a`.
1570+
1571+
`rtol` (optional): Shall be a scalar `real` value specifying the relative tolerance for singular value cutoff.
1572+
If not provided, the default threshold is \( \text{max}(m, n) \cdot \epsilon \), where \( \epsilon \) is the
1573+
machine precision for the element type of `a`.
1574+
1575+
`err` (optional): Shall be a `type(linalg_state_type)` value. It is an `intent(out)` argument.
1576+
1577+
### Return value
1578+
1579+
Computes the Moore-Penrose pseudo-inverse of the matrix \( A \), \( A^{+} \), and returns it in matrix `pinva`.
1580+
1581+
Raises `LINALG_ERROR` if the underlying SVD did not converge.
1582+
Raises `LINALG_VALUE_ERROR` if `pinva` and `a` have degenerate or incompatible sizes.
1583+
If `err` is not present, exceptions trigger an `error stop`.
1584+
1585+
### Example
1586+
1587+
```fortran
1588+
{!example/linalg/example_pseudoinverse.f90!}
1589+
```
1590+
1591+
## `.pinv.` - Moore-Penrose Pseudo-Inverse operator
1592+
1593+
### Status
1594+
1595+
Experimental
1596+
1597+
### Description
1598+
1599+
This operator returns the Moore-Penrose pseudo-inverse of a `real` or `complex` matrix \( A \).
1600+
The pseudo-inverse \( A^{+} \) is computed using Singular Value Decomposition (SVD), and singular values
1601+
below a given threshold are treated as zero.
1602+
1603+
This interface is equivalent to the function [[stdlib_linalg(module):pinv(interface)]].
1604+
1605+
### Syntax
1606+
1607+
`b = ` [[stdlib_linalg(module):operator(.pinv.)(interface)]] `a`
1608+
1609+
### Arguments
1610+
1611+
`a`: Shall be a rank-2 array of any `real` or `complex` kinds, with arbitrary dimensions \( m \times n \). It is an `intent(in)` argument.
1612+
1613+
### Return value
1614+
1615+
Returns a rank-2 array with the same type, kind, and rank as `a`, that contains the Moore-Penrose pseudo-inverse of `a`.
1616+
1617+
If an exception occurs, or if the input matrix is degenerate (e.g., rank-deficient), the returned matrix will contain `NaN`s.
1618+
For more detailed error handling, it is recommended to use the `subroutine` or `function` interfaces.
1619+
1620+
### Example
1621+
1622+
```fortran
1623+
{!example/linalg/example_pseudoinverse.f90!}
1624+
```
1625+
14901626
## `get_norm` - Computes the vector norm of a generic-rank array.
14911627

14921628
### Status

example/linalg/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ ADD_EXAMPLE(inverse_operator)
1717
ADD_EXAMPLE(inverse_function)
1818
ADD_EXAMPLE(inverse_inplace)
1919
ADD_EXAMPLE(inverse_subroutine)
20+
ADD_EXAMPLE(pseudoinverse)
2021
ADD_EXAMPLE(outer_product)
2122
ADD_EXAMPLE(eig)
2223
ADD_EXAMPLE(eigh)
Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
! Matrix pseudo-inversion example: function, subroutine, and operator interfaces
2+
program example_pseudoinverse
3+
use stdlib_linalg, only: pinv, pseudoinvert, operator(.pinv.), linalg_state_type
4+
implicit none(type,external)
5+
6+
real :: A(15,5), Am1(5,15)
7+
type(linalg_state_type) :: state
8+
integer :: i, j
9+
real, parameter :: tol = sqrt(epsilon(0.0))
10+
11+
! Generate random matrix A (15x15)
12+
call random_number(A)
13+
14+
! Pseudo-inverse: Function interfcae
15+
Am1 = pinv(A, err=state)
16+
print *, 'Max error (function) : ', maxval(abs(A-matmul(A, matmul(Am1,A))))
17+
18+
! User threshold
19+
Am1 = pinv(A, rtol=0.001, err=state)
20+
print *, 'Max error (rtol=0.001): ', maxval(abs(A-matmul(A, matmul(Am1,A))))
21+
22+
! Pseudo-inverse: Subroutine interface
23+
call pseudoinvert(A, Am1, err=state)
24+
25+
print *, 'Max error (subroutine): ', maxval(abs(A-matmul(A, matmul(Am1,A))))
26+
27+
! Operator interface
28+
Am1 = .pinv.A
29+
30+
print *, 'Max error (operator) : ', maxval(abs(A-matmul(A, matmul(Am1,A))))
31+
32+
end program example_pseudoinverse

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ set(fppFiles
3232
stdlib_linalg_determinant.fypp
3333
stdlib_linalg_qr.fypp
3434
stdlib_linalg_inverse.fypp
35+
stdlib_linalg_pinv.fypp
3536
stdlib_linalg_norms.fypp
3637
stdlib_linalg_state.fypp
3738
stdlib_linalg_svd.fypp

src/stdlib_io.fypp

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -167,7 +167,7 @@ contains
167167
read (s,*,iostat=ios,iomsg=iomsg) d(i, :)
168168

169169
if (ios/=0) then
170-
write(msgout,1) trim(iomsg),i,trim(filename)
170+
write(msgout,1) trim(iomsg),size(d,2),i,trim(filename)
171171
call error_stop(msg=trim(msgout))
172172
end if
173173

@@ -178,7 +178,7 @@ contains
178178
read (s,fmt_,iostat=ios,iomsg=iomsg) d(i, :)
179179

180180
if (ios/=0) then
181-
write(msgout,1) trim(iomsg),i,trim(filename)
181+
write(msgout,1) trim(iomsg),size(d,2),i,trim(filename)
182182
call error_stop(msg=trim(msgout))
183183
end if
184184

@@ -187,7 +187,7 @@ contains
187187

188188
close(s)
189189

190-
1 format('loadtxt: error <',a,'> reading line ',i0,' of ',a,'.')
190+
1 format('loadtxt: error <',a,'> reading ',i0,' values from line ',i0,' of ',a,'.')
191191

192192
end subroutine loadtxt_${t1[0]}$${k1}$
193193
#:endfor
@@ -230,14 +230,14 @@ contains
230230
iostat=ios,iomsg=iomsg) d(i, :)
231231

232232
if (ios/=0) then
233-
write(msgout,1) trim(iomsg),i,trim(filename)
233+
write(msgout,1) trim(iomsg),size(d,2),i,trim(filename)
234234
call error_stop(msg=trim(msgout))
235235
end if
236236

237237
end do
238238
close(s)
239239

240-
1 format('savetxt: error <',a,'> writing line ',i0,' of ',a,'.')
240+
1 format('savetxt: error <',a,'> writing ',i0,' values to line ',i0,' of ',a,'.')
241241

242242
end subroutine savetxt_${t1[0]}$${k1}$
243243
#:endfor

src/stdlib_linalg.fypp

Lines changed: 128 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -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

Comments
 (0)