-
Notifications
You must be signed in to change notification settings - Fork 173
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
linalg: Eigenvalues and Eigenvectors (#816)
- Loading branch information
Showing
11 changed files
with
1,287 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,26 @@ | ||
! Eigendecomposition of a real square matrix | ||
program example_eig | ||
use stdlib_linalg, only: eig | ||
implicit none | ||
|
||
integer :: i | ||
real, allocatable :: A(:,:) | ||
complex, allocatable :: lambda(:),vectors(:,:) | ||
|
||
! Decomposition of this square matrix | ||
! NB Fortran is column-major -> transpose input | ||
A = transpose(reshape( [ [2, 2, 4], & | ||
[1, 3, 5], & | ||
[2, 3, 4] ], [3,3] )) | ||
|
||
! Get eigenvalues and right eigenvectors | ||
allocate(lambda(3),vectors(3,3)) | ||
|
||
call eig(A, lambda, right=vectors) | ||
|
||
do i=1,3 | ||
print *, 'eigenvalue ',i,': ',lambda(i) | ||
print *, 'eigenvector ',i,': ',vectors(:,i) | ||
end do | ||
|
||
end program example_eig |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,38 @@ | ||
! Eigendecomposition of a real symmetric matrix | ||
program example_eigh | ||
use stdlib_linalg, only: eigh | ||
implicit none | ||
|
||
integer :: i | ||
real, allocatable :: A(:,:),lambda(:),vectors(:,:) | ||
complex, allocatable :: cA(:,:),cvectors(:,:) | ||
|
||
! Decomposition of this symmetric matrix | ||
! NB Fortran is column-major -> transpose input | ||
A = transpose(reshape( [ [2, 1, 4], & | ||
[1, 3, 5], & | ||
[4, 5, 4] ], [3,3] )) | ||
|
||
! Note: real symmetric matrices have real (orthogonal) eigenvalues and eigenvectors | ||
allocate(lambda(3),vectors(3,3)) | ||
call eigh(A, lambda, vectors=vectors) | ||
|
||
print *, 'Real matrix' | ||
do i=1,3 | ||
print *, 'eigenvalue ',i,': ',lambda(i) | ||
print *, 'eigenvector ',i,': ',vectors(:,i) | ||
end do | ||
|
||
! Complex hermitian matrices have real (orthogonal) eigenvalues and complex eigenvectors | ||
cA = A | ||
|
||
allocate(cvectors(3,3)) | ||
call eigh(cA, lambda, vectors=cvectors) | ||
|
||
print *, 'Complex matrix' | ||
do i=1,3 | ||
print *, 'eigenvalue ',i,': ',lambda(i) | ||
print *, 'eigenvector ',i,': ',cvectors(:,i) | ||
end do | ||
|
||
end program example_eigh |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,24 @@ | ||
! Eigenvalues of a general real / complex matrix | ||
program example_eigvals | ||
use stdlib_linalg, only: eigvals | ||
implicit none | ||
|
||
integer :: i | ||
real, allocatable :: A(:,:),lambda(:) | ||
complex, allocatable :: cA(:,:),clambda(:) | ||
|
||
! NB Fortran is column-major -> transpose input | ||
A = transpose(reshape( [ [2, 8, 4], & | ||
[1, 3, 5], & | ||
[9, 5,-2] ], [3,3] )) | ||
|
||
! Note: real symmetric matrix | ||
lambda = eigvals(A) | ||
print *, 'Real matrix eigenvalues: ',lambda | ||
|
||
! Complex general matrix | ||
cA = cmplx(A, -2*A) | ||
clambda = eigvals(cA) | ||
print *, 'Complex matrix eigenvalues: ',clambda | ||
|
||
end program example_eigvals |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,25 @@ | ||
! Eigenvalues of a real symmetric / complex hermitian matrix | ||
program example_eigvalsh | ||
use stdlib_linalg, only: eigvalsh | ||
implicit none | ||
|
||
integer :: i | ||
real, allocatable :: A(:,:),lambda(:) | ||
complex, allocatable :: cA(:,:) | ||
|
||
! Decomposition of this symmetric matrix | ||
! NB Fortran is column-major -> transpose input | ||
A = transpose(reshape( [ [2, 1, 4], & | ||
[1, 3, 5], & | ||
[4, 5, 4] ], [3,3] )) | ||
|
||
! Note: real symmetric matrices have real (orthogonal) eigenvalues and eigenvectors | ||
lambda = eigvalsh(A) | ||
print *, 'Symmetric matrix eigenvalues: ',lambda | ||
|
||
! Complex hermitian matrices have real (orthogonal) eigenvalues and complex eigenvectors | ||
cA = A | ||
lambda = eigvalsh(cA) | ||
print *, 'Hermitian matrix eigenvalues: ',lambda | ||
|
||
end program example_eigvalsh |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.