Skip to content

Commit cc129c6

Browse files
authored
linalg: Eigenvalues and Eigenvectors (fortran-lang#816)
2 parents d996e43 + d433869 commit cc129c6

11 files changed

+1287
-2
lines changed

doc/specs/stdlib_linalg.md

Lines changed: 176 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.
@@ -899,6 +901,180 @@ Exceptions trigger an `error stop`.
899901
{!example/linalg/example_determinant2.f90!}
900902
```
901903

904+
## `eig` - Eigenvalues and Eigenvectors of a Square Matrix
905+
906+
### Status
907+
908+
Experimental
909+
910+
### Description
911+
912+
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.
913+
914+
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 \).
915+
Both `left` and `right` are rank-2 arrays, where eigenvectors are stored as columns.
916+
The solver is based on LAPACK's `*GEEV` backends.
917+
918+
### Syntax
919+
920+
`call ` [[stdlib_linalg(module):eig(interface)]] `(a, lambda [, right] [,left] [,overwrite_a] [,err])`
921+
922+
### Arguments
923+
924+
`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.
925+
926+
`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.
927+
928+
`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.
929+
930+
`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.
931+
932+
`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.
933+
934+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
935+
936+
### Return value
937+
938+
Raises `LINALG_ERROR` if the calculation did not converge.
939+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
940+
Raises `LINALG_VALUE_ERROR` if the `real` component is only requested, but the eigenvalues have non-trivial imaginary parts.
941+
If `err` is not present, exceptions trigger an `error stop`.
942+
943+
### Example
944+
945+
```fortran
946+
{!example/linalg/example_eig.f90!}
947+
```
948+
949+
## `eigh` - Eigenvalues and Eigenvectors of a Real symmetric or Complex Hermitian Square Matrix
950+
951+
### Status
952+
953+
Experimental
954+
955+
### Description
956+
957+
This subroutine computes the solution to the eigendecomposition \( A \cdot \bar{v} - \lambda \cdot \bar{v} \),
958+
where \( A \) is a square, full-rank, `real` symmetric \( A = A^T \) or `complex` Hermitian \( A = A^H \) matrix.
959+
960+
Result array `lambda` returns the `real` eigenvalues of \( A \). The user can request the orthogonal eigenvectors
961+
to be returned: on output `vectors` may contain the matrix of eigenvectors, returned as a column.
962+
963+
Normally, only the lower triangular part of \( A \) is accessed. On input, `logical` flag `upper_a`
964+
allows the user to request what triangular part of the matrix should be used.
965+
966+
The solver is based on LAPACK's `*SYEV` and `*HEEV` backends.
967+
968+
### Syntax
969+
970+
`call ` [[stdlib_linalg(module):eigh(interface)]] `(a, lambda [, vectors] [, upper_a] [, overwrite_a] [,err])`
971+
972+
### Arguments
973+
974+
`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.
975+
976+
`lambda`: Shall be a `complex` rank-1 array of the same precision as `a`, containing the eigenvalues. It is an `intent(out)` argument.
977+
978+
`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.
979+
980+
`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.
981+
982+
`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.
983+
984+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
985+
986+
### Return value
987+
988+
Raises `LINALG_ERROR` if the calculation did not converge.
989+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
990+
If `err` is not present, exceptions trigger an `error stop`.
991+
992+
### Example
993+
994+
```fortran
995+
{!example/linalg/example_eigh.f90!}
996+
```
997+
998+
## `eigvals` - Eigenvalues of a Square Matrix
999+
1000+
### Status
1001+
1002+
Experimental
1003+
1004+
### Description
1005+
1006+
This function returns the eigenvalues to matrix \( A \): a square, full-rank, `real` or `complex` matrix.
1007+
The eigenvalues are solutions to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \).
1008+
1009+
Result array `lambda` is `complex`, and returns the eigenvalues of \( A \).
1010+
The solver is based on LAPACK's `*GEEV` backends.
1011+
1012+
### Syntax
1013+
1014+
`lambda = ` [[stdlib_linalg(module):eigvals(interface)]] `(a, [,err])`
1015+
1016+
### Arguments
1017+
1018+
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
1019+
1020+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1021+
1022+
### Return value
1023+
1024+
Returns a `complex` array containing the eigenvalues of `a`.
1025+
1026+
Raises `LINALG_ERROR` if the calculation did not converge.
1027+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1028+
If `err` is not present, exceptions trigger an `error stop`.
1029+
1030+
1031+
### Example
1032+
1033+
```fortran
1034+
{!example/linalg/example_eigvals.f90!}
1035+
```
1036+
1037+
## `eigvalsh` - Eigenvalues of a Real Symmetric or Complex Hermitian Square Matrix
1038+
1039+
### Status
1040+
1041+
Experimental
1042+
1043+
### Description
1044+
1045+
This function returns the eigenvalues to matrix \( A \): a where \( A \) is a square, full-rank,
1046+
`real` symmetric \( A = A^T \) or `complex` Hermitian \( A = A^H \) matrix.
1047+
The eigenvalues are solutions to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \).
1048+
1049+
Result array `lambda` is `real`, and returns the eigenvalues of \( A \).
1050+
The solver is based on LAPACK's `*SYEV` and `*HEEV` backends.
1051+
1052+
### Syntax
1053+
1054+
`lambda = ` [[stdlib_linalg(module):eigvalsh(interface)]] `(a, [, upper_a] [,err])`
1055+
1056+
### Arguments
1057+
1058+
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
1059+
1060+
`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.
1061+
1062+
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1063+
1064+
### Return value
1065+
1066+
Returns a `real` array containing the eigenvalues of `a`.
1067+
1068+
Raises `LINALG_ERROR` if the calculation did not converge.
1069+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1070+
If `err` is not present, exceptions trigger an `error stop`.
1071+
1072+
### Example
1073+
1074+
```fortran
1075+
{!example/linalg/example_eigvalsh.f90!}
1076+
```
1077+
9021078
## `svd` - Compute the singular value decomposition of a rank-2 array (matrix).
9031079

9041080
### Status
@@ -989,4 +1165,3 @@ Exceptions trigger an `error stop`, unless argument `err` is present.
9891165
```fortran
9901166
{!example/linalg/example_svdvals.f90!}
9911167
```
992-

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

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_state.fypp
3334
stdlib_linalg_svd.fypp

0 commit comments

Comments
 (0)