Skip to content

Commit b5b86a7

Browse files
authored
linalg eig: generalized eigenvalue problem (#909)
2 parents 05e44f0 + 565e8d7 commit b5b86a7

7 files changed

+480
-73
lines changed

doc/specs/stdlib_linalg.md

+38-13
Original file line numberDiff line numberDiff line change
@@ -1091,20 +1091,30 @@ Stable
10911091

10921092
### Description
10931093

1094-
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.
1094+
This subroutine computes the solution to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \),
1095+
where \( A \) is a square, full-rank, `real` or `complex` matrix, or to the generalized eigenproblem \( A \cdot \bar{v} - \lambda \cdot B \cdot \bar{v} \),
1096+
where \( B \) is a square matrix with the same type, kind and size as \( A \).
10951097

10961098
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 \).
10971099
Both `left` and `right` are rank-2 arrays, where eigenvectors are stored as columns.
1098-
The solver is based on LAPACK's `*GEEV` backends.
1100+
The solver is based on LAPACK's `*GEEV` (standard eigenproblem) and `*GGEV` (generalized eigenproblem) backends.
10991101

11001102
### Syntax
11011103

1104+
For the standard eigenproblem:
1105+
11021106
`call ` [[stdlib_linalg(module):eig(interface)]] `(a, lambda [, right] [,left] [,overwrite_a] [,err])`
11031107

1108+
For the generalized eigenproblem:
1109+
1110+
`call ` [[stdlib_linalg(module):eig(interface)]] `(a, b, lambda [, right] [, left] [, overwrite_a] [, overwrite_b] [, err])
1111+
11041112
### Arguments
11051113

11061114
`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.
11071115

1116+
`b`: `real` or `complex` square array containing the second coefficient matrix. If `overwrite_b=.false.`, it is an `intent(in)` argument. Otherwise, it is an `intent(inout)` argument and is destroyed by the call.
1117+
11081118
`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.
11091119

11101120
`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.
@@ -1113,6 +1123,8 @@ The solver is based on LAPACK's `*GEEV` backends.
11131123

11141124
`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.
11151125

1126+
`overwrite_b` (optional): Shall be an input logical flag. If `.true.`, input matrix `b` will be used as temporary storage and overwritten. This avoids internal data allocation. This is an `intent(in)` argument.
1127+
11161128
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
11171129

11181130
### Return value
@@ -1185,28 +1197,41 @@ Stable
11851197

11861198
### Description
11871199

1188-
This function returns the eigenvalues to matrix \( A \): a square, full-rank, `real` or `complex` matrix.
1189-
The eigenvalues are solutions to the eigenproblem \( A \cdot \bar{v} - \lambda \cdot \bar{v} \).
1200+
This function computes the eigenvalues for either a standard or generalized eigenproblem:
11901201

1191-
Result array `lambda` is `complex`, and returns the eigenvalues of \( A \).
1192-
The solver is based on LAPACK's `*GEEV` backends.
1202+
- **Standard eigenproblem**: \( A \cdot \bar{v} - \lambda \cdot \bar{v} \), where \( A \) is a square, full-rank `real` or `complex` matrix.
1203+
- **Generalized eigenproblem**: \( A \cdot \bar{v} - \lambda \cdot B \cdot \bar{v} \), where \( B \) is a square matrix with the same type and kind as \( A \).
1204+
1205+
The eigenvalues are stored in the result array `lambda`, which is `complex` (even for real input matrices).
1206+
The solver uses LAPACK's `*GEEV` and `*GGEV` backends for the standard and generalized problems, respectively.
11931207

11941208
### Syntax
11951209

1196-
`lambda = ` [[stdlib_linalg(module):eigvals(interface)]] `(a, [,err])`
1210+
For the standard eigenproblem:
1211+
1212+
`lambda = ` [[stdlib_linalg(module):eigvals(interface)]] `(a [, err])`
1213+
1214+
For the generalized eigenproblem:
1215+
1216+
`lambda = ` [[stdlib_linalg(module):eigvals(interface)]] `(a, b [, err])`
11971217

11981218
### Arguments
11991219

1200-
`a` : `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
1220+
`a`:
1221+
Shall be a `real` or `complex` square array containing the coefficient matrix. It is an `intent(in)` argument.
12011222

1202-
`err` (optional): Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
1223+
`b` (optional):
1224+
Shall be a `real` or `complex` square array containing the second coefficient matrix for the generalized problem. It is an `intent(in)` argument.
12031225

1204-
### Return value
1226+
`err` (optional):
1227+
Shall be a `type(linalg_state_type)` value. This is an `intent(out)` argument.
12051228

1206-
Returns a `complex` array containing the eigenvalues of `a`.
1229+
### Return Value
12071230

1208-
Raises `LINALG_ERROR` if the calculation did not converge.
1209-
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
1231+
Returns a `complex` rank-1 array containing the eigenvalues of the problem.
1232+
1233+
Raises `LINALG_ERROR` if the calculation did not converge.
1234+
Raises `LINALG_VALUE_ERROR` if any matrix or arrays have invalid/incompatible sizes.
12101235
If `err` is not present, exceptions trigger an `error stop`.
12111236

12121237
### Example

example/linalg/CMakeLists.txt

+2
Original file line numberDiff line numberDiff line change
@@ -21,8 +21,10 @@ ADD_EXAMPLE(pseudoinverse)
2121
ADD_EXAMPLE(outer_product)
2222
ADD_EXAMPLE(eig)
2323
ADD_EXAMPLE(eigh)
24+
ADD_EXAMPLE(eig_generalized)
2425
ADD_EXAMPLE(eigvals)
2526
ADD_EXAMPLE(eigvalsh)
27+
ADD_EXAMPLE(eigvals_generalized)
2628
ADD_EXAMPLE(trace)
2729
ADD_EXAMPLE(state1)
2830
ADD_EXAMPLE(state2)
+30
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
! Eigendecomposition of a real square matrix for the generalized eigenproblem
2+
program example_eig_generalized
3+
use stdlib_linalg, only: eig, eye
4+
implicit none
5+
6+
integer :: i
7+
real, allocatable :: A(:,:), B(:,:)
8+
complex, allocatable :: lambda(:), vectors(:,:)
9+
10+
! Matrices for the generalized eigenproblem: A * v = lambda * B * v
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+
B = eye(3)
17+
18+
! Allocate eigenvalues and right eigenvectors
19+
allocate(lambda(3), vectors(3,3))
20+
21+
! Get eigenvalues and right eigenvectors for the generalized problem
22+
call eig(A, B, lambda, right=vectors)
23+
24+
do i = 1, 3
25+
print *, 'Eigenvalue ', i, ': ', lambda(i)
26+
print *, 'Eigenvector ', i, ': ', vectors(:,i)
27+
end do
28+
29+
end program example_eig_generalized
30+
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
! Eigenvalues of a general real/complex matrix for the generalized eigenproblem
2+
program example_eigvals_generalized
3+
use stdlib_linalg, only: eigvals, eye
4+
implicit none
5+
6+
real, allocatable :: A(:,:), B(:,:), lambda(:)
7+
complex, allocatable :: cA(:,:), cB(:,:), clambda(:)
8+
9+
! NB Fortran is column-major -> transpose input
10+
A = transpose(reshape([ [2, 8, 4], &
11+
[1, 3, 5], &
12+
[9, 5,-2] ], [3,3]))
13+
14+
B = eye(3)
15+
16+
! Real generalized eigenproblem
17+
lambda = eigvals(A, B)
18+
print *, 'Real generalized matrix eigenvalues: ', lambda
19+
20+
! Complex generalized eigenproblem
21+
cA = cmplx(A, -2*A)
22+
cB = cmplx(B, 0.5*B)
23+
clambda = eigvals(cA, cB)
24+
print *, 'Complex generalized matrix eigenvalues: ', clambda
25+
26+
end program example_eigvals_generalized

src/stdlib_linalg.fypp

+44-22
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,9 @@
55
#:set RHS_SYMBOL = [ranksuffix(r) for r in [1,2]]
66
#:set RHS_EMPTY = [emptyranksuffix(r) for r in [1,2]]
77
#:set ALL_RHS = list(zip(RHS_SYMBOL,RHS_SUFFIX,RHS_EMPTY))
8+
#:set EIG_PROBLEM = ["standard", "generalized"]
9+
#:set EIG_FUNCTION = ["geev","ggev"]
10+
#:set EIG_PROBLEM_LIST = list(zip(EIG_PROBLEM, EIG_FUNCTION))
811
module stdlib_linalg
912
!!Provides a support for various linear algebra procedures
1013
!! ([Specification](../page/specs/stdlib_linalg.html))
@@ -1084,12 +1087,17 @@ module stdlib_linalg
10841087
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
10851088
!!
10861089
#:for rk,rt,ri in RC_KINDS_TYPES
1087-
#:if rk!="xdp"
1088-
module subroutine stdlib_linalg_eig_${ri}$(a,lambda,right,left,overwrite_a,err)
1090+
#:for ep,ei in EIG_PROBLEM_LIST
1091+
module subroutine stdlib_linalg_eig_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,lambda,right,left, &
1092+
overwrite_a#{if ei=='ggev'}#,overwrite_b#{endif}#,err)
10891093
!! Eigendecomposition of matrix A returning an array `lambda` of eigenvalues,
10901094
!! and optionally right or left eigenvectors.
10911095
!> Input matrix A[m,n]
10921096
${rt}$, intent(inout), target :: a(:,:)
1097+
#:if ei=='ggev'
1098+
!> Generalized problem matrix B[n,n]
1099+
${rt}$, intent(inout), target :: b(:,:)
1100+
#:endif
10931101
!> Array of eigenvalues
10941102
complex(${rk}$), intent(out) :: lambda(:)
10951103
!> The columns of RIGHT contain the right eigenvectors of A
@@ -1098,19 +1106,25 @@ module stdlib_linalg
10981106
complex(${rk}$), optional, intent(out), target :: left(:,:)
10991107
!> [optional] Can A data be overwritten and destroyed?
11001108
logical(lk), optional, intent(in) :: overwrite_a
1109+
#:if ei=='ggev'
1110+
!> [optional] Can B data be overwritten and destroyed? (default: no)
1111+
logical(lk), optional, intent(in) :: overwrite_b
1112+
#:endif
11011113
!> [optional] state return flag. On error if not requested, the code will stop
11021114
type(linalg_state_type), optional, intent(out) :: err
1103-
end subroutine stdlib_linalg_eig_${ri}$
1104-
#:endif
1105-
#:endfor
1106-
#:for rk,rt,ri in REAL_KINDS_TYPES
1107-
#:if rk!="xdp"
1108-
module subroutine stdlib_linalg_real_eig_${ri}$(a,lambda,right,left,overwrite_a,err)
1115+
end subroutine stdlib_linalg_eig_${ep}$_${ri}$
1116+
1117+
module subroutine stdlib_linalg_real_eig_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,lambda,right,left, &
1118+
overwrite_a#{if ei=='ggev'}#,overwrite_b#{endif}#,err)
11091119
!! Eigendecomposition of matrix A returning an array `lambda` of real eigenvalues,
11101120
!! and optionally right or left eigenvectors. Returns an error if the eigenvalues had
11111121
!! non-trivial imaginary parts.
11121122
!> Input matrix A[m,n]
11131123
${rt}$, intent(inout), target :: a(:,:)
1124+
#:if ei=='ggev'
1125+
!> Generalized problem matrix B[n,n]
1126+
${rt}$, intent(inout), target :: b(:,:)
1127+
#:endif
11141128
!> Array of real eigenvalues
11151129
real(${rk}$), intent(out) :: lambda(:)
11161130
!> The columns of RIGHT contain the right eigenvectors of A
@@ -1119,11 +1133,15 @@ module stdlib_linalg
11191133
complex(${rk}$), optional, intent(out), target :: left(:,:)
11201134
!> [optional] Can A data be overwritten and destroyed?
11211135
logical(lk), optional, intent(in) :: overwrite_a
1136+
#:if ei=='ggev'
1137+
!> [optional] Can B data be overwritten and destroyed? (default: no)
1138+
logical(lk), optional, intent(in) :: overwrite_b
1139+
#:endif
11221140
!> [optional] state return flag. On error if not requested, the code will stop
11231141
type(linalg_state_type), optional, intent(out) :: err
1124-
end subroutine stdlib_linalg_real_eig_${ri}$
1125-
#:endif
1142+
end subroutine stdlib_linalg_real_eig_${ep}$_${ri}$
11261143
#:endfor
1144+
#:endfor
11271145
end interface eig
11281146

11291147
! Eigenvalues of a square matrix
@@ -1147,25 +1165,33 @@ module stdlib_linalg
11471165
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
11481166
!!
11491167
#:for rk,rt,ri in RC_KINDS_TYPES
1150-
#:if rk!="xdp"
1151-
module function stdlib_linalg_eigvals_${ri}$(a,err) result(lambda)
1168+
#:for ep,ei in EIG_PROBLEM_LIST
1169+
module function stdlib_linalg_eigvals_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,err) result(lambda)
11521170
!! Return an array of eigenvalues of matrix A.
11531171
!> Input matrix A[m,n]
1154-
${rt}$, intent(in), target :: a(:,:)
1172+
${rt}$, intent(in), dimension(:,:), target :: a
1173+
#:if ei=='ggev'
1174+
!> Generalized problem matrix B[n,n]
1175+
${rt}$, intent(inout), dimension(:,:), target :: b
1176+
#:endif
11551177
!> [optional] state return flag. On error if not requested, the code will stop
11561178
type(linalg_state_type), intent(out) :: err
11571179
!> Array of singular values
11581180
complex(${rk}$), allocatable :: lambda(:)
1159-
end function stdlib_linalg_eigvals_${ri}$
1181+
end function stdlib_linalg_eigvals_${ep}$_${ri}$
11601182

1161-
module function stdlib_linalg_eigvals_noerr_${ri}$(a) result(lambda)
1183+
module function stdlib_linalg_eigvals_noerr_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#) result(lambda)
11621184
!! Return an array of eigenvalues of matrix A.
11631185
!> Input matrix A[m,n]
1164-
${rt}$, intent(in), target :: a(:,:)
1186+
${rt}$, intent(in), dimension(:,:), target :: a
1187+
#:if ei=='ggev'
1188+
!> Generalized problem matrix B[n,n]
1189+
${rt}$, intent(inout), dimension(:,:), target :: b
1190+
#:endif
11651191
!> Array of singular values
11661192
complex(${rk}$), allocatable :: lambda(:)
1167-
end function stdlib_linalg_eigvals_noerr_${ri}$
1168-
#:endif
1193+
end function stdlib_linalg_eigvals_noerr_${ep}$_${ri}$
1194+
#:endfor
11691195
#:endfor
11701196
end interface eigvals
11711197

@@ -1194,7 +1220,6 @@ module stdlib_linalg
11941220
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
11951221
!!
11961222
#:for rk,rt,ri in RC_KINDS_TYPES
1197-
#:if rk!="xdp"
11981223
module subroutine stdlib_linalg_eigh_${ri}$(a,lambda,vectors,upper_a,overwrite_a,err)
11991224
!! Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array `lambda`
12001225
!! of eigenvalues, and optionally right or left eigenvectors.
@@ -1211,7 +1236,6 @@ module stdlib_linalg
12111236
!> [optional] state return flag. On error if not requested, the code will stop
12121237
type(linalg_state_type), optional, intent(out) :: err
12131238
end subroutine stdlib_linalg_eigh_${ri}$
1214-
#:endif
12151239
#:endfor
12161240
end interface eigh
12171241

@@ -1239,7 +1263,6 @@ module stdlib_linalg
12391263
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
12401264
!!
12411265
#:for rk,rt,ri in RC_KINDS_TYPES
1242-
#:if rk!="xdp"
12431266
module function stdlib_linalg_eigvalsh_${ri}$(a,upper_a,err) result(lambda)
12441267
!! Return an array of eigenvalues of real symmetric / complex hermitian A
12451268
!> Input matrix A[m,n]
@@ -1261,7 +1284,6 @@ module stdlib_linalg
12611284
!> Array of singular values
12621285
real(${rk}$), allocatable :: lambda(:)
12631286
end function stdlib_linalg_eigvalsh_noerr_${ri}$
1264-
#:endif
12651287
#:endfor
12661288
end interface eigvalsh
12671289

0 commit comments

Comments
 (0)