Skip to content

Commit f344f07

Browse files
committed
add examples
1 parent 7d49905 commit f344f07

File tree

3 files changed

+62
-0
lines changed

3 files changed

+62
-0
lines changed

example/linalg/CMakeLists.txt

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,10 @@ ADD_EXAMPLE(inverse_subroutine)
1919
ADD_EXAMPLE(outer_product)
2020
ADD_EXAMPLE(eig)
2121
ADD_EXAMPLE(eigh)
22+
ADD_EXAMPLE(eig_generalized)
2223
ADD_EXAMPLE(eigvals)
2324
ADD_EXAMPLE(eigvalsh)
25+
ADD_EXAMPLE(eigvals_generalized)
2426
ADD_EXAMPLE(trace)
2527
ADD_EXAMPLE(state1)
2628
ADD_EXAMPLE(state2)
Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,32 @@
1+
! Eigendecomposition of a real square matrix for the generalized eigenproblem
2+
program example_eig_generalized
3+
use stdlib_linalg, only: eig
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 = transpose(reshape([ [1, 0, 0], &
17+
[0, 1, 0], &
18+
[0, 0, 1] ], [3,3]))
19+
20+
! Allocate eigenvalues and right eigenvectors
21+
allocate(lambda(3), vectors(3,3))
22+
23+
! Get eigenvalues and right eigenvectors for the generalized problem
24+
call eig(A, B, lambda, right=vectors)
25+
26+
do i = 1, 3
27+
print *, 'Eigenvalue ', i, ': ', lambda(i)
28+
print *, 'Eigenvector ', i, ': ', vectors(:,i)
29+
end do
30+
31+
end program example_eig_generalized
32+
Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
! Eigenvalues of a general real/complex matrix for the generalized eigenproblem
2+
program example_eigvals_generalized
3+
use stdlib_linalg, only: eigvals
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 = transpose(reshape([ [1, 0, 0], &
15+
[0, 1, 0], &
16+
[0, 0, 1] ], [3,3]))
17+
18+
! Real generalized eigenproblem
19+
lambda = eigvals(A, B)
20+
print *, 'Real generalized matrix eigenvalues: ', lambda
21+
22+
! Complex generalized eigenproblem
23+
cA = cmplx(A, -2*A)
24+
cB = cmplx(B, 0.5*B)
25+
clambda = eigvals(cA, cB)
26+
print *, 'Complex generalized matrix eigenvalues: ', clambda
27+
28+
end program example_eigvals_generalized

0 commit comments

Comments
 (0)