Skip to content

Commit 2944e6e

Browse files
authored
Merge branch 'fortran-lang:master' into sphinx-doc
2 parents 587fa02 + 70d34a4 commit 2944e6e

34 files changed

+26170
-23761
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
@@ -98,7 +98,8 @@ end interface axpy
9898
Note that the 128-bit functions are only provided by `stdlib` and always point to the internal implementation.
9999
Because 128-bit precision is identified as [stdlib_kinds(module):qp], initials for 128-bit procedures were
100100
labelled as `q` (quadruple-precision reals) and `w` ("wide" or quadruple-precision complex numbers).
101-
Extended precision ([stdlib_kinds(module):xdp]) calculations are currently not supported.
101+
Extended precision ([stdlib_kinds(module):xdp]) calculations are labelled as `x` (extended-precision reals).
102+
and `y` (extended-precision complex numbers).
102103

103104
### Example
104105

@@ -775,7 +776,7 @@ Result vector `x` returns the approximate solution that minimizes the 2-norm \(
775776

776777
`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.
777778

778-
`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.
779+
`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.
779780

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

@@ -877,15 +878,15 @@ This interface is equivalent to the `pure` version of determinant [[stdlib_linal
877878

878879
### Syntax
879880

880-
`c = ` [[stdlib_linalg(module):operator(.det.)(interface)]] `(a)`
881+
`c = ` [[stdlib_linalg(module):operator(.det.)(interface)]] `a`
881882

882883
### Arguments
883884

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

886887
### Return value
887888

888-
Returns a real scalar value that represents the determinnt of the matrix.
889+
Returns a real scalar value that represents the determinant of the matrix.
889890

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

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

include/common.fypp

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -60,6 +60,19 @@
6060
#:set CMPLX_INIT = CMPLX_INIT + ["w"]
6161
#:endif
6262

63+
#! BLAS/LAPACK complex->real kind initial conversion
64+
#! Converts a BLAS/LAPACK complex kind initial to a real kind initial
65+
#!
66+
#! Args:
67+
#! ci (character): Complex kind initial in ["c","z","y","w"]
68+
#!
69+
#! Returns:
70+
#! Real kind initial in ["s","d","x","q"] or an empty string on invalid input
71+
#!
72+
#:def c2ri(cmplx)
73+
$:"s" if cmplx=="c" else "d" if cmplx=="z" else "x" if cmplx=="y" else "q" if cmplx=="w" else "ERROR"
74+
#:enddef
75+
6376
#! Complex types to be considered during templating
6477
#:set CMPLX_TYPES = ["complex({})".format(k) for k in CMPLX_KINDS]
6578

src/CMakeLists.txt

Lines changed: 1 addition & 0 deletions
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)