Skip to content

Commit 7393a18

Browse files
authored
Merge branch 'master' into qr
2 parents 8827bf7 + c8fa301 commit 7393a18

12 files changed

+835
-6
lines changed

API-doc-FORD-file.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ project_website: https://stdlib.fortran-lang.org
4343
favicon: doc/media/favicon.ico
4444
license: by-sa
4545
author: fortran-lang/stdlib contributors
46-
author_pic: https://fortran-lang.org/assets/img/fortran_logo_512x512.png
46+
author_pic: https://fortran-lang.org/en/_static/fortran-logo-256x256.png
4747
4848
github: https://github.com/fortran-lang
4949
twitter: https://twitter.com/fortranlang

doc/specs/stdlib_linalg.md

Lines changed: 127 additions & 4 deletions
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.
@@ -1242,3 +1243,125 @@ Exceptions trigger an `error stop`, unless argument `err` is present.
12421243
```fortran
12431244
{!example/linalg/example_svdvals.f90!}
12441245
```
1246+
1247+
## `.inv.` - Inverse operator of a square matrix
1248+
1249+
### Status
1250+
1251+
Experimental
1252+
1253+
### Description
1254+
1255+
This operator returns the inverse of a `real` or `complex` square matrix \( A \).
1256+
The inverse \( A^{-1} \) is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1257+
1258+
This interface is equivalent to the function [[stdlib_linalg(module):inv(interface)]].
1259+
1260+
### Syntax
1261+
1262+
`b = ` [[stdlib_linalg(module):operator(.inv.)(interface)]] `a`
1263+
1264+
### Arguments
1265+
1266+
`a`: Shall be a rank-2 square array of any `real` or `complex` kinds. It is an `intent(in)` argument.
1267+
1268+
### Return value
1269+
1270+
Returns a rank-2 square array with the same type, kind and rank as `a`, that contains the inverse of `a`.
1271+
1272+
If an exception occurred on input errors, or singular matrix, `NaN`s will be returned.
1273+
For fine-grained error control in case of singular matrices prefer the `subroutine` and the `function`
1274+
interfaces.
1275+
1276+
1277+
### Example
1278+
1279+
```fortran
1280+
{!example/linalg/example_inverse_operator.f90!}
1281+
```
1282+
1283+
## `invert` - Inversion of a square matrix
1284+
1285+
### Status
1286+
1287+
Experimental
1288+
1289+
### Description
1290+
1291+
This subroutine inverts a square `real` or `complex` matrix in-place.
1292+
The inverse \( A^{-1} \) is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1293+
1294+
On return, the input matrix `a` is replaced by its inverse.
1295+
The solver is based on LAPACK's `*GETRF` and `*GETRI` backends.
1296+
1297+
### Syntax
1298+
1299+
`call ` [[stdlib_linalg(module):invert(interface)]] `(a, [,inva] [, pivot] [, err])`
1300+
1301+
### Arguments
1302+
1303+
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix.
1304+
If `inva` is provided, it is an `intent(in)` argument.
1305+
If `inva` is not provided, it is an `intent(inout)` argument: on output, it is replaced by the inverse of `a`.
1306+
1307+
`inva` (optional): Shall be a rank-2, square, `real` or `complex` array with the same size, and kind as `a`.
1308+
On output, it contains the inverse of `a`.
1309+
1310+
`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.
1311+
1312+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1313+
1314+
### Return value
1315+
1316+
Computes the inverse of the matrix \( A \), \(A^{-1}\, and returns it either in \( A \) or in another matrix.
1317+
1318+
Raises `LINALG_ERROR` if the matrix is singular or has invalid size.
1319+
Raises `LINALG_VALUE_ERROR` if `inva` and `a` do not have the same size.
1320+
If `err` is not present, exceptions trigger an `error stop`.
1321+
1322+
### Example
1323+
1324+
```fortran
1325+
{!example/linalg/example_inverse_inplace.f90!}
1326+
```
1327+
1328+
```fortran
1329+
{!example/linalg/example_inverse_subroutine.f90!}
1330+
```
1331+
1332+
## `inv` - Inverse of a square matrix.
1333+
1334+
### Status
1335+
1336+
Experimental
1337+
1338+
### Description
1339+
1340+
This function returns the inverse of a square `real` or `complex` matrix in-place.
1341+
The inverse, \( A^{-1} \), is defined such that \( A \cdot A^{-1} = A^{-1} \cdot A = I_n \).
1342+
1343+
The solver is based on LAPACK's `*GETRF` and `*GETRI` backends.
1344+
1345+
### Syntax
1346+
1347+
`b ` [[stdlib_linalg(module):inv(interface)]] `(a, [, err])`
1348+
1349+
### Arguments
1350+
1351+
`a`: Shall be a rank-2, square, `real` or `complex` array containing the coefficient matrix. It is an `intent(inout)` argument.
1352+
1353+
`err` (optional): Shall be a `type(linalg_state_type)` value. It is an `intent(out)` argument.
1354+
1355+
### Return value
1356+
1357+
Returns an array value of the same type, kind and rank as `a`, that contains the inverse matrix \(A^{-1}\).
1358+
1359+
Raises `LINALG_ERROR` if the matrix is singular or has invalid size.
1360+
If `err` is not present, exceptions trigger an `error stop`.
1361+
1362+
### Example
1363+
1364+
```fortran
1365+
{!example/linalg/example_inverse_function.f90!}
1366+
```
1367+

example/linalg/CMakeLists.txt

Lines changed: 4 additions & 0 deletions
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)
Lines changed: 22 additions & 0 deletions
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
Lines changed: 23 additions & 0 deletions
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
Lines changed: 22 additions & 0 deletions
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
Lines changed: 22 additions & 0 deletions
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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,6 +31,7 @@ set(fppFiles
3131
stdlib_linalg_solve.fypp
3232
stdlib_linalg_determinant.fypp
3333
stdlib_linalg_qr.fypp
34+
stdlib_linalg_inverse.fypp
3435
stdlib_linalg_state.fypp
3536
stdlib_linalg_svd.fypp
3637
stdlib_optval.fypp

0 commit comments

Comments
 (0)