Skip to content

Commit b5f7f21

Browse files
committed
add examples: eig, eigh, eigvals, eigvalsh
1 parent 15b73fc commit b5f7f21

File tree

5 files changed

+121
-0
lines changed

5 files changed

+121
-0
lines changed

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

example/linalg/example_eigh.f90

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

example/linalg/example_eigvals.f90

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

example/linalg/example_eigvalsh.f90

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

0 commit comments

Comments
 (0)