Skip to content

Commit c8fa301

Browse files
authored
linalg: Matrix Inverse (#828)
2 parents e01b3a3 + bb3f7e4 commit c8fa301

11 files changed

+834
-5
lines changed

doc/specs/stdlib_linalg.md

+127-4
Original file line numberDiff line numberDiff line change
@@ -104,7 +104,8 @@ end interface axpy
104104
Note that the 128-bit functions are only provided by `stdlib` and always point to the internal implementation.
105105
Because 128-bit precision is identified as [stdlib_kinds(module):qp], initials for 128-bit procedures were
106106
labelled as `q` (quadruple-precision reals) and `w` ("wide" or quadruple-precision complex numbers).
107-
Extended precision ([stdlib_kinds(module):xdp]) calculations are currently not supported.
107+
Extended precision ([stdlib_kinds(module):xdp]) calculations are labelled as `x` (extended-precision reals).
108+
and `y` (extended-precision complex numbers).
108109

109110
### Example
110111

@@ -779,7 +780,7 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
779780

780781
`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.
781782

782-
`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.
783+
`singvals` (optional): Shall be a `real` rank-1 array of the same kind `a` and size at least `min(m,n)`, returning the list of singular values `s(i)>=cond*maxval(s)` from the internal SVD, in descending order of magnitude. It is an `intent(out)` argument.
783784

784785
`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.
785786

@@ -881,15 +882,15 @@ This interface is equivalent to the `pure` version of determinant [[stdlib_linal
881882

882883
### Syntax
883884

884-
`c = ` [[stdlib_linalg(module):operator(.det.)(interface)]] `(a)`
885+
`c = ` [[stdlib_linalg(module):operator(.det.)(interface)]] `a`
885886

886887
### Arguments
887888

888889
`a`: Shall be a rank-2 square array of any `real` or `complex` kinds. It is an `intent(in)` argument.
889890

890891
### Return value
891892

892-
Returns a real scalar value that represents the determinnt of the matrix.
893+
Returns a real scalar value that represents the determinant of the matrix.
893894

894895
Raises `LINALG_ERROR` if the matrix is singular.
895896
Raises `LINALG_VALUE_ERROR` if the matrix is non-square.
@@ -1165,3 +1166,125 @@ Exceptions trigger an `error stop`, unless argument `err` is present.
11651166
```fortran
11661167
{!example/linalg/example_svdvals.f90!}
11671168
```
1169+
1170+
## `.inv.` - Inverse operator of a square matrix
1171+
1172+
### Status
1173+
1174+
Experimental
1175+
1176+
### Description
1177+
1178+
This operator returns the inverse of a `real` or `complex` square matrix \( A \).
1179+
The inverse \( A^{-1} \) is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1180+
1181+
This interface is equivalent to the function [[stdlib_linalg(module):inv(interface)]].
1182+
1183+
### Syntax
1184+
1185+
`b = ` [[stdlib_linalg(module):operator(.inv.)(interface)]] `a`
1186+
1187+
### Arguments
1188+
1189+
`a`: Shall be a rank-2 square array of any `real` or `complex` kinds. It is an `intent(in)` argument.
1190+
1191+
### Return value
1192+
1193+
Returns a rank-2 square array with the same type, kind and rank as `a`, that contains the inverse of `a`.
1194+
1195+
If an exception occurred on input errors, or singular matrix, `NaN`s will be returned.
1196+
For fine-grained error control in case of singular matrices prefer the `subroutine` and the `function`
1197+
interfaces.
1198+
1199+
1200+
### Example
1201+
1202+
```fortran
1203+
{!example/linalg/example_inverse_operator.f90!}
1204+
```
1205+
1206+
## `invert` - Inversion of a square matrix
1207+
1208+
### Status
1209+
1210+
Experimental
1211+
1212+
### Description
1213+
1214+
This subroutine inverts a square `real` or `complex` matrix in-place.
1215+
The inverse \( A^{-1} \) is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1216+
1217+
On return, the input matrix `a` is replaced by its inverse.
1218+
The solver is based on LAPACK's `*GETRF` and `*GETRI` backends.
1219+
1220+
### Syntax
1221+
1222+
`call ` [[stdlib_linalg(module):invert(interface)]] `(a, [,inva] [, pivot] [, err])`
1223+
1224+
### Arguments
1225+
1226+
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix.
1227+
If `inva` is provided, it is an `intent(in)` argument.
1228+
If `inva` is not provided, it is an `intent(inout)` argument: on output, it is replaced by the inverse of `a`.
1229+
1230+
`inva` (optional): Shall be a rank-2, square, `real` or `complex` array with the same size, and kind as `a`.
1231+
On output, it contains the inverse of `a`.
1232+
1233+
`pivot` (optional): Shall be a rank-1 array of the same kind and matrix dimension as `a`, that contains the diagonal pivot indices on return. It is an `intent(inout)` argument.
1234+
1235+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1236+
1237+
### Return value
1238+
1239+
Computes the inverse of the matrix \( A \), \(A^{-1}\, and returns it either in \( A \) or in another matrix.
1240+
1241+
Raises `LINALG_ERROR` if the matrix is singular or has invalid size.
1242+
Raises `LINALG_VALUE_ERROR` if `inva` and `a` do not have the same size.
1243+
If `err` is not present, exceptions trigger an `error stop`.
1244+
1245+
### Example
1246+
1247+
```fortran
1248+
{!example/linalg/example_inverse_inplace.f90!}
1249+
```
1250+
1251+
```fortran
1252+
{!example/linalg/example_inverse_subroutine.f90!}
1253+
```
1254+
1255+
## `inv` - Inverse of a square matrix.
1256+
1257+
### Status
1258+
1259+
Experimental
1260+
1261+
### Description
1262+
1263+
This function returns the inverse of a square `real` or `complex` matrix in-place.
1264+
The inverse, \( A^{-1} \), is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1265+
1266+
The solver is based on LAPACK's `*GETRF` and `*GETRI` backends.
1267+
1268+
### Syntax
1269+
1270+
`b ` [[stdlib_linalg(module):inv(interface)]] `(a, [, err])`
1271+
1272+
### Arguments
1273+
1274+
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
1275+
1276+
`err` (optional): Shall be a `type(linalg_state_type)` value. It is an `intent(out)` argument.
1277+
1278+
### Return value
1279+
1280+
Returns an array value of the same type, kind and rank as `a`, that contains the inverse matrix \(A^{-1}\).
1281+
1282+
Raises `LINALG_ERROR` if the matrix is singular or has invalid size.
1283+
If `err` is not present, exceptions trigger an `error stop`.
1284+
1285+
### Example
1286+
1287+
```fortran
1288+
{!example/linalg/example_inverse_function.f90!}
1289+
```
1290+

example/linalg/CMakeLists.txt

+4
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,10 @@ ADD_EXAMPLE(is_skew_symmetric)
1212
ADD_EXAMPLE(is_square)
1313
ADD_EXAMPLE(is_symmetric)
1414
ADD_EXAMPLE(is_triangular)
15+
ADD_EXAMPLE(inverse_operator)
16+
ADD_EXAMPLE(inverse_function)
17+
ADD_EXAMPLE(inverse_inplace)
18+
ADD_EXAMPLE(inverse_subroutine)
1519
ADD_EXAMPLE(outer_product)
1620
ADD_EXAMPLE(eig)
1721
ADD_EXAMPLE(eigh)
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! Matrix inversion example: function interface
2+
program example_inverse_function
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: inv,eye
5+
implicit none
6+
7+
real(dp) :: A(2,2), Am1(2,2)
8+
9+
! Input matrix (NB Fortran is column major! input columns then transpose)
10+
A = transpose(reshape( [4, 3, &
11+
3, 2], [2,2] ))
12+
13+
! Invert matrix
14+
Am1 = inv(A)
15+
16+
print *, ' |',Am1(1,:),'|' ! | -2 3 |
17+
print *, ' inv(A)= |',Am1(2,:),'|' ! | 3 -4 |
18+
19+
! Final check
20+
print *, 'CHECK passed? ',matmul(A,Am1)==eye(2)
21+
22+
end program example_inverse_function
+23
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
! Matrix inversion example: in-place inversion
2+
program example_inverse_inplace
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: invert,eye
5+
implicit none
6+
7+
real(dp) :: A(2,2), Am1(2,2)
8+
9+
! Input matrix (NB Fortran is column major! input columns then transpose)
10+
A = transpose(reshape( [4, 3, &
11+
3, 2], [2,2] ))
12+
Am1 = A
13+
14+
! Invert matrix
15+
call invert(Am1)
16+
17+
print *, ' |',Am1(1,:),'|' ! | -2 3 |
18+
print *, ' inv(A)= |',Am1(2,:),'|' ! | 3 -4 |
19+
20+
! Final check
21+
print *, 'CHECK passed? ',matmul(A,Am1)==eye(2)
22+
23+
end program example_inverse_inplace
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! Matrix inversion example: operator interface
2+
program example_inverse_operator
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: operator(.inv.),eye
5+
implicit none
6+
7+
real(dp) :: A(2,2), Am1(2,2)
8+
9+
! Input matrix (NB Fortran is column major! input columns then transpose)
10+
A = transpose(reshape( [4, 3, &
11+
3, 2], [2,2] ))
12+
13+
! Invert matrix
14+
Am1 = .inv.A
15+
16+
print *, ' |',Am1(1,:),'|' ! | -2 3 |
17+
print *, ' inv(A)= |',Am1(2,:),'|' ! | 3 -4 |
18+
19+
! Final check
20+
print *, 'CHECK passed? ',matmul(A,Am1)==eye(2)
21+
22+
end program example_inverse_operator
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
! Matrix inversion example: subroutine interface
2+
program example_inverse_subroutine
3+
use stdlib_linalg_constants, only: dp
4+
use stdlib_linalg, only: invert,eye
5+
implicit none
6+
7+
real(dp) :: A(2,2), Am1(2,2)
8+
9+
! Input matrix (NB Fortran is column major! input columns then transpose)
10+
A = transpose(reshape( [4, 3, &
11+
3, 2], [2,2] ))
12+
13+
! Invert matrix
14+
call invert(A,Am1)
15+
16+
print *, ' |',Am1(1,:),'|' ! | -2 3 |
17+
print *, ' inv(A)= |',Am1(2,:),'|' ! | 3 -4 |
18+
19+
! Final check
20+
print *, 'CHECK passed? ',matmul(A,Am1)==eye(2)
21+
22+
end program example_inverse_subroutine

src/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ set(fppFiles
3030
stdlib_linalg_eigenvalues.fypp
3131
stdlib_linalg_solve.fypp
3232
stdlib_linalg_determinant.fypp
33+
stdlib_linalg_inverse.fypp
3334
stdlib_linalg_state.fypp
3435
stdlib_linalg_svd.fypp
3536
stdlib_optval.fypp

0 commit comments

Comments
 (0)