Skip to content

Commit 68ece36

Browse files
authored
Merge branch 'master' into qr
2 parents fcb5306 + 4859081 commit 68ece36

34 files changed

+26659
-23755
lines changed

CHANGELOG.md

Lines changed: 40 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,43 @@
1+
# Version 0.7.0
2+
3+
Full release notes available at [v0.7.0] tag.
4+
5+
[v0.7.0]: https://github.com/fortran-lang/stdlib/releases/tag/v0.7.0
6+
7+
- new module `stdlib_constants`
8+
[#800](https://github.com/fortran-lang/stdlib/pull/800)
9+
- Many mathematical constants and most common physical ([codata](https://codata.org)) constants
10+
11+
Changes to existing scripts and modules
12+
- changes in CI
13+
- Use of `fortran-setup` for GCC, Intel LLVM and Intel Classic
14+
[#834](https://github.com/fortran-lang/stdlib/pull/834)
15+
- change in module `stdlib_hashmaps`
16+
- Support of hash map key generic interfaces
17+
[#827](https://github.com/fortran-lang/stdlib/pull/827)
18+
- changes in module `stdlib_io`
19+
- Addition of a Fortran format specifier in `loadtxt`
20+
[#805](https://github.com/fortran-lang/stdlib/pull/805)
21+
- changes in module `stdlib_linalg`
22+
- Support of extended and quad precision checking
23+
[#821](https://github.com/fortran-lang/stdlib/pull/821)
24+
- Several fixes
25+
[#815](https://github.com/fortran-lang/stdlib/pull/815)
26+
[#818](https://github.com/fortran-lang/stdlib/pull/818)
27+
[#826](https://github.com/fortran-lang/stdlib/pull/826)
28+
[#830](https://github.com/fortran-lang/stdlib/pull/830)
29+
[#836](https://github.com/fortran-lang/stdlib/pull/836)
30+
- New procedures for Eigenvalues and Eigenvectors computation: `eig`, `eigh`, `eigvals`, `eigvalsh`
31+
[#816](https://github.com/fortran-lang/stdlib/pull/816)
32+
- New procedures for Singular Value Decomposition: `svd`, `svdvals`
33+
[#808](https://github.com/fortran-lang/stdlib/pull/808)
34+
- changes in module `stdlib_sorting`
35+
- Renamed variable from `int_size` to `int_index`
36+
[#824](https://github.com/fortran-lang/stdlib/pull/824)
37+
- Support of `int32` `index` array in `sort_index`
38+
[#829](https://github.com/fortran-lang/stdlib/pull/829)
39+
40+
141
# Version 0.6.1
242

343
Full release notes available at [v0.6.1] tag.

VERSION

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
0.6.1
1+
0.7.0

doc/specs/stdlib_linalg.md

Lines changed: 175 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -687,6 +687,8 @@ Expert (`Pure`) interface:
687687

688688
`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.
689689

690+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
691+
690692
### Return value
691693

692694
For a full-rank matrix, returns an array value that represents the solution to the linear system of equations.
@@ -975,6 +977,179 @@ This subroutine computes the internal working space requirements for the QR fact
975977
{!example/linalg/example_qr_space.f90!}
976978
```
977979

980+
## `eig` - Eigenvalues and Eigenvectors of a Square Matrix
981+
982+
### Status
983+
984+
Experimental
985+
986+
### Description
987+
988+
This subroutine computes the solution to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \), where \( A \) is a square, full-rank, `real` or `complex` matrix.
989+
990+
Result array `lambda` returns the eigenvalues of \( A \). The user can request eigenvectors to be returned: if provided, on output `left` will contain the left eigenvectors, `right` the right eigenvectors of \( A \).
991+
Both `left` and `right` are rank-2 arrays, where eigenvectors are stored as columns.
992+
The solver is based on LAPACK's `*GEEV` backends.
993+
994+
### Syntax
995+
996+
`call ` [[stdlib_linalg(module):eig(interface)]] `(a, lambda [, right] [,left] [,overwrite_a] [,err])`
997+
998+
### Arguments
999+
1000+
`a` : `real` or `complex` square array containing the coefficient matrix. If `overwrite_a=.false.`, it is an `intent(in)` argument. Otherwise, it is an `intent(inout)` argument and is destroyed by the call.
1001+
1002+
`lambda`: Shall be a `complex` or `real` rank-1 array of the same kind as `a`, containing the eigenvalues, or their `real` component only. It is an `intent(out)` argument.
1003+
1004+
`right` (optional): Shall be a `complex` rank-2 array of the same size and kind as `a`, containing the right eigenvectors of `a`. It is an `intent(out)` argument.
1005+
1006+
`left` (optional): Shall be a `complex` rank-2 array of the same size and kind as `a`, containing the left eigenvectors of `a`. It is an `intent(out)` argument.
1007+
1008+
`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.
1009+
1010+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1011+
1012+
### Return value
1013+
1014+
Raises `LINALG_ERROR` if the calculation did not converge.
1015+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1016+
Raises `LINALG_VALUE_ERROR` if the `real` component is only requested, but the eigenvalues have non-trivial imaginary parts.
1017+
If `err` is not present, exceptions trigger an `error stop`.
1018+
1019+
### Example
1020+
1021+
```fortran
1022+
{!example/linalg/example_eig.f90!}
1023+
```
1024+
1025+
## `eigh` - Eigenvalues and Eigenvectors of a Real symmetric or Complex Hermitian Square Matrix
1026+
1027+
### Status
1028+
1029+
Experimental
1030+
1031+
### Description
1032+
1033+
This subroutine computes the solution to the eigendecomposition \( A \cdot \bar{v} - \lambda \cdot \bar{v} \),
1034+
where \( A \) is a square, full-rank, `real` symmetric \( A = A^T \) or `complex` Hermitian \( A = A^H \) matrix.
1035+
1036+
Result array `lambda` returns the `real` eigenvalues of \( A \). The user can request the orthogonal eigenvectors
1037+
to be returned: on output `vectors` may contain the matrix of eigenvectors, returned as a column.
1038+
1039+
Normally, only the lower triangular part of \( A \) is accessed. On input, `logical` flag `upper_a`
1040+
allows the user to request what triangular part of the matrix should be used.
1041+
1042+
The solver is based on LAPACK's `*SYEV` and `*HEEV` backends.
1043+
1044+
### Syntax
1045+
1046+
`call ` [[stdlib_linalg(module):eigh(interface)]] `(a, lambda [, vectors] [, upper_a] [, overwrite_a] [,err])`
1047+
1048+
### Arguments
1049+
1050+
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument. If `overwrite_a=.true.`, it is an `intent(inout)` argument and is destroyed by the call.
1051+
1052+
`lambda`: Shall be a `complex` rank-1 array of the same precision as `a`, containing the eigenvalues. It is an `intent(out)` argument.
1053+
1054+
`vectors` (optional): Shall be a rank-2 array of the same type, size and kind as `a`, containing the eigenvectors of `a`. It is an `intent(out)` argument.
1055+
1056+
`upper_a` (optional): Shall be an input `logical` flag. If `.true.`, the upper triangular part of `a` will be accessed. Otherwise, the lower triangular part will be accessed. It is an `intent(in)` argument.
1057+
1058+
`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.
1059+
1060+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1061+
1062+
### Return value
1063+
1064+
Raises `LINALG_ERROR` if the calculation did not converge.
1065+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1066+
If `err` is not present, exceptions trigger an `error stop`.
1067+
1068+
### Example
1069+
1070+
```fortran
1071+
{!example/linalg/example_eigh.f90!}
1072+
```
1073+
1074+
## `eigvals` - Eigenvalues of a Square Matrix
1075+
1076+
### Status
1077+
1078+
Experimental
1079+
1080+
### Description
1081+
1082+
This function returns the eigenvalues to matrix \( A \): a square, full-rank, `real` or `complex` matrix.
1083+
The eigenvalues are solutions to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \).
1084+
1085+
Result array `lambda` is `complex`, and returns the eigenvalues of \( A \).
1086+
The solver is based on LAPACK's `*GEEV` backends.
1087+
1088+
### Syntax
1089+
1090+
`lambda = ` [[stdlib_linalg(module):eigvals(interface)]] `(a, [,err])`
1091+
1092+
### Arguments
1093+
1094+
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
1095+
1096+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1097+
1098+
### Return value
1099+
1100+
Returns a `complex` array containing the eigenvalues of `a`.
1101+
1102+
Raises `LINALG_ERROR` if the calculation did not converge.
1103+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1104+
If `err` is not present, exceptions trigger an `error stop`.
1105+
1106+
### Example
1107+
1108+
```fortran
1109+
{!example/linalg/example_eigvals.f90!}
1110+
```
1111+
1112+
## `eigvalsh` - Eigenvalues of a Real Symmetric or Complex Hermitian Square Matrix
1113+
1114+
### Status
1115+
1116+
Experimental
1117+
1118+
### Description
1119+
1120+
This function returns the eigenvalues to matrix \( A \): a where \( A \) is a square, full-rank,
1121+
`real` symmetric \( A = A^T \) or `complex` Hermitian \( A = A^H \) matrix.
1122+
The eigenvalues are solutions to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \).
1123+
1124+
Result array `lambda` is `real`, and returns the eigenvalues of \( A \).
1125+
The solver is based on LAPACK's `*SYEV` and `*HEEV` backends.
1126+
1127+
### Syntax
1128+
1129+
`lambda = ` [[stdlib_linalg(module):eigvalsh(interface)]] `(a, [, upper_a] [,err])`
1130+
1131+
### Arguments
1132+
1133+
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
1134+
1135+
`upper_a` (optional): Shall be an input logical flag. If `.true.`, the upper triangular part of `a` will be used accessed. Otherwise, the lower triangular part will be accessed (default). It is an `intent(in)` argument.
1136+
1137+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1138+
1139+
### Return value
1140+
1141+
Returns a `real` array containing the eigenvalues of `a`.
1142+
1143+
Raises `LINALG_ERROR` if the calculation did not converge.
1144+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1145+
If `err` is not present, exceptions trigger an `error stop`.
1146+
1147+
### Example
1148+
1149+
```fortran
1150+
{!example/linalg/example_eigvalsh.f90!}
1151+
```
1152+
9781153
## `svd` - Compute the singular value decomposition of a rank-2 array (matrix).
9791154

9801155
### Status
@@ -1066,4 +1241,3 @@ Exceptions trigger an `error stop`, unless argument `err` is present.
10661241
```fortran
10671242
{!example/linalg/example_svdvals.f90!}
10681243
```
1069-

example/linalg/CMakeLists.txt

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,10 @@ ADD_EXAMPLE(is_square)
1313
ADD_EXAMPLE(is_symmetric)
1414
ADD_EXAMPLE(is_triangular)
1515
ADD_EXAMPLE(outer_product)
16+
ADD_EXAMPLE(eig)
17+
ADD_EXAMPLE(eigh)
18+
ADD_EXAMPLE(eigvals)
19+
ADD_EXAMPLE(eigvalsh)
1620
ADD_EXAMPLE(trace)
1721
ADD_EXAMPLE(state1)
1822
ADD_EXAMPLE(state2)

example/linalg/example_eig.f90

Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
! Eigendecomposition of a real square matrix
2+
program example_eig
3+
use stdlib_linalg, only: eig
4+
implicit none
5+
6+
integer :: i
7+
real, allocatable :: A(:,:)
8+
complex, allocatable :: lambda(:),vectors(:,:)
9+
10+
! Decomposition of this square matrix
11+
! NB Fortran is column-major -> transpose input
12+
A = transpose(reshape( [ [2, 2, 4], &
13+
[1, 3, 5], &
14+
[2, 3, 4] ], [3,3] ))
15+
16+
! Get eigenvalues and right eigenvectors
17+
allocate(lambda(3),vectors(3,3))
18+
19+
call eig(A, lambda, right=vectors)
20+
21+
do i=1,3
22+
print *, 'eigenvalue ',i,': ',lambda(i)
23+
print *, 'eigenvector ',i,': ',vectors(:,i)
24+
end do
25+
26+
end program example_eig

example/linalg/example_eigh.f90

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,38 @@
1+
! Eigendecomposition of a real symmetric matrix
2+
program example_eigh
3+
use stdlib_linalg, only: eigh
4+
implicit none
5+
6+
integer :: i
7+
real, allocatable :: A(:,:),lambda(:),vectors(:,:)
8+
complex, allocatable :: cA(:,:),cvectors(:,:)
9+
10+
! Decomposition of this symmetric matrix
11+
! NB Fortran is column-major -> transpose input
12+
A = transpose(reshape( [ [2, 1, 4], &
13+
[1, 3, 5], &
14+
[4, 5, 4] ], [3,3] ))
15+
16+
! Note: real symmetric matrices have real (orthogonal) eigenvalues and eigenvectors
17+
allocate(lambda(3),vectors(3,3))
18+
call eigh(A, lambda, vectors=vectors)
19+
20+
print *, 'Real matrix'
21+
do i=1,3
22+
print *, 'eigenvalue ',i,': ',lambda(i)
23+
print *, 'eigenvector ',i,': ',vectors(:,i)
24+
end do
25+
26+
! Complex hermitian matrices have real (orthogonal) eigenvalues and complex eigenvectors
27+
cA = A
28+
29+
allocate(cvectors(3,3))
30+
call eigh(cA, lambda, vectors=cvectors)
31+
32+
print *, 'Complex matrix'
33+
do i=1,3
34+
print *, 'eigenvalue ',i,': ',lambda(i)
35+
print *, 'eigenvector ',i,': ',cvectors(:,i)
36+
end do
37+
38+
end program example_eigh

example/linalg/example_eigvals.f90

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
! Eigenvalues of a general real / complex matrix
2+
program example_eigvals
3+
use stdlib_linalg, only: eigvals
4+
implicit none
5+
6+
integer :: i
7+
real, allocatable :: A(:,:),lambda(:)
8+
complex, allocatable :: cA(:,:),clambda(:)
9+
10+
! NB Fortran is column-major -> transpose input
11+
A = transpose(reshape( [ [2, 8, 4], &
12+
[1, 3, 5], &
13+
[9, 5,-2] ], [3,3] ))
14+
15+
! Note: real symmetric matrix
16+
lambda = eigvals(A)
17+
print *, 'Real matrix eigenvalues: ',lambda
18+
19+
! Complex general matrix
20+
cA = cmplx(A, -2*A)
21+
clambda = eigvals(cA)
22+
print *, 'Complex matrix eigenvalues: ',clambda
23+
24+
end program example_eigvals

example/linalg/example_eigvalsh.f90

Lines changed: 25 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
! Eigenvalues of a real symmetric / complex hermitian matrix
2+
program example_eigvalsh
3+
use stdlib_linalg, only: eigvalsh
4+
implicit none
5+
6+
integer :: i
7+
real, allocatable :: A(:,:),lambda(:)
8+
complex, allocatable :: cA(:,:)
9+
10+
! Decomposition of this symmetric matrix
11+
! NB Fortran is column-major -> transpose input
12+
A = transpose(reshape( [ [2, 1, 4], &
13+
[1, 3, 5], &
14+
[4, 5, 4] ], [3,3] ))
15+
16+
! Note: real symmetric matrices have real (orthogonal) eigenvalues and eigenvectors
17+
lambda = eigvalsh(A)
18+
print *, 'Symmetric matrix eigenvalues: ',lambda
19+
20+
! Complex hermitian matrices have real (orthogonal) eigenvalues and complex eigenvectors
21+
cA = A
22+
lambda = eigvalsh(cA)
23+
print *, 'Hermitian matrix eigenvalues: ',lambda
24+
25+
end program example_eigvalsh

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: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,8 @@ set(fppFiles
2727
stdlib_linalg_outer_product.fypp
2828
stdlib_linalg_kronecker.fypp
2929
stdlib_linalg_cross_product.fypp
30-
stdlib_linalg_solve.fypp
30+
stdlib_linalg_eigenvalues.fypp
31+
stdlib_linalg_solve.fypp
3132
stdlib_linalg_determinant.fypp
3233
stdlib_linalg_qr.fypp
3334
stdlib_linalg_state.fypp

0 commit comments

Comments
 (0)