Skip to content

Commit 1ebf374

Browse files
committed
add documentation
1 parent 892308f commit 1ebf374

File tree

2 files changed

+93
-13
lines changed

2 files changed

+93
-13
lines changed

src/stdlib_linalg.fypp

Lines changed: 85 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -556,8 +556,27 @@ module stdlib_linalg
556556
#:endfor
557557
end interface
558558

559-
interface eig
560-
!! Eigendecomposition of a square matrix: return eigenvalues, and optionally eigenvectors
559+
! Eigendecomposition of a square matrix: eigenvalues, and optionally eigenvectors
560+
interface eig
561+
!! version: experimental
562+
!!
563+
!! Solves the eigendecomposition \( A \cdot \bar{v} - \lambda \cdot \bar{v} \) for square matrix \( A \).
564+
!! ([Specification](../page/specs/stdlib_linalg.html#eig-eigenvalues-and-eigenvectors-of-a-square-matrix))
565+
!!
566+
!!### Summary
567+
!! Subroutine interface for computing eigenvalues and eigenvectors of a square matrix.
568+
!!
569+
!!### Description
570+
!!
571+
!! This interface provides methods for computing the eigenvalues, and optionally eigenvectors,
572+
!! of a general square matrix. Supported data types include `real` and `complex`, and no assumption is
573+
!! made on the matrix structure. The user may request either left, right, or both
574+
!! eigenvectors to be returned. They are returned as columns of a square matrix with the same size as `A`.
575+
!! Preallocated space for both eigenvalues `lambda` and the eigenvector matrices must be user-provided.
576+
!!
577+
!!@note The solution is based on LAPACK's general eigenproblem solvers `*GEEV`.
578+
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
579+
!!
561580
#:for rk,rt,ri in RC_KINDS_TYPES
562581
#:if rk!="xdp"
563582
module subroutine stdlib_linalg_eig_${ri}$(a,lambda,right,left,overwrite_a,err)
@@ -580,8 +599,26 @@ module stdlib_linalg
580599
#:endfor
581600
end interface eig
582601

602+
! Eigenvalues of a square matrix
583603
interface eigvals
584-
!! Eigenvalues of a square matrix
604+
!! version: experimental
605+
!!
606+
!! Returns the eigenvalues \( lambda \), \( A \cdot \bar{v} - \lambda \cdot \bar{v} \), for square matrix \( A \).
607+
!! ([Specification](../page/specs/stdlib_linalg.html#eigvals-eigenvalues-of-a-square-matrix))
608+
!!
609+
!!### Summary
610+
!! Function interface for computing the eigenvalues of a square matrix.
611+
!!
612+
!!### Description
613+
!!
614+
!! This interface provides functions for returning the eigenvalues of a general square matrix.
615+
!! Supported data types include `real` and `complex`, and no assumption is made on the matrix structure.
616+
!! An `error stop` is thrown in case of failure; otherwise, error information can be returned
617+
!! as an optional `type(linalg_state_type)` output flag.
618+
!!
619+
!!@note The solution is based on LAPACK's general eigenproblem solvers `*GEEV`.
620+
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
621+
!!
585622
#:for rk,rt,ri in RC_KINDS_TYPES
586623
#:if rk!="xdp"
587624
module function stdlib_linalg_eigvals_${ri}$(a,err) result(lambda)
@@ -605,8 +642,30 @@ module stdlib_linalg
605642
#:endfor
606643
end interface eigvals
607644

645+
! Eigendecomposition of a real symmetric or complex hermitian matrix
608646
interface eigh
609-
!! Eigendecomposition of a real symmetric or complex hermitian matrix
647+
!! version: experimental
648+
!!
649+
!! Solves the eigendecomposition \( A \cdot \bar{v} - \lambda \cdot \bar{v} \) for a real symmetric
650+
!! \( A = A^T \) or complex Hermitian \( A = A^H \) square matrix.
651+
!! ([Specification](../page/specs/stdlib_linalg.html#eigh-eigenvalues-and-eigenvectors-of-a-real-symmetric-or-complex-hermitian-square-matrix))
652+
!!
653+
!!### Summary
654+
!! Subroutine interface for computing eigenvalues and eigenvectors of a real symmetric or complex Hermitian square matrix.
655+
!!
656+
!!### Description
657+
!!
658+
!! This interface provides methods for computing the eigenvalues, and optionally eigenvectors,
659+
!! of a real symmetric or complex Hermitian square matrix. Supported data types include `real` and `complex`.
660+
!! The matrix must be symmetric (if `real`) or Hermitian (if `complex`). Only the lower or upper
661+
!! half of the matrix is accessed, and the user can select which using the optional `upper_a`
662+
!! flag (default: use lower half). The vectors are orthogonal, and may be returned as columns of an optional
663+
!! matrix `vectors` with the same kind and size as `A`.
664+
!! Preallocated space for both eigenvalues `lambda` and the eigenvector matrix must be user-provided.
665+
!!
666+
!!@note The solution is based on LAPACK's eigenproblem solvers `*SYEV`/`*HEEV`.
667+
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
668+
!!
610669
#:for rk,rt,ri in RC_KINDS_TYPES
611670
#:if rk!="xdp"
612671
module subroutine stdlib_linalg_eigh_${ri}$(a,lambda,vectors,upper_a,overwrite_a,err)
@@ -629,8 +688,29 @@ module stdlib_linalg
629688
#:endfor
630689
end interface eigh
631690

691+
! Eigenvalues of a real symmetric or complex hermitian matrix
632692
interface eigvalsh
633-
!! Eigenvalues of a real symmetric or complex hermitian matrix
693+
!! version: experimental
694+
!!
695+
!! Returns the eigenvalues \( lambda \), \( A \cdot \bar{v} - \lambda \cdot \bar{v} \), for a real
696+
!! symmetric \( A = A^T \) or complex Hermitian \( A = A^H \) square matrix.
697+
!! ([Specification](../page/specs/stdlib_linalg.html#eigvalsh-eigenvalues-of-a-real-symmetric-or-complex-hermitian-square-matrix))
698+
!!
699+
!!### Summary
700+
!! Function interface for computing the eigenvalues of a real symmetric or complex hermitian square matrix.
701+
!!
702+
!!### Description
703+
!!
704+
!! This interface provides functions for returning the eigenvalues of a real symmetric or complex Hermitian
705+
!! square matrix. Supported data types include `real` and `complex`. The matrix must be symmetric
706+
!! (if `real`) or Hermitian (if `complex`). Only the lower or upper half of the matrix is accessed,
707+
!! and the user can select which using the optional `upper_a` flag (default: use lower half).
708+
!! An `error stop` is thrown in case of failure; otherwise, error information can be returned
709+
!! as an optional `type(linalg_state_type)` output flag.
710+
!!
711+
!!@note The solution is based on LAPACK's eigenproblem solvers `*SYEV`/`*HEEV`.
712+
!!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
713+
!!
634714
#:for rk,rt,ri in RC_KINDS_TYPES
635715
#:if rk!="xdp"
636716
module function stdlib_linalg_eigvalsh_${ri}$(a,upper_a,err) result(lambda)

src/stdlib_linalg_eigenvalues.fypp

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
9999
${rt}$, intent(in), target :: a(:,:)
100100
!> [optional] state return flag. On error if not requested, the code will stop
101101
type(linalg_state_type), intent(out) :: err
102-
!> Array of singular values
102+
!> Array of eigenvalues
103103
complex(${rk}$), allocatable :: lambda(:)
104104

105105
!> Create
@@ -125,7 +125,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
125125
!! Return an array of eigenvalues of matrix A.
126126
!> Input matrix A[m,n]
127127
${rt}$, intent(in), target :: a(:,:)
128-
!> Array of singular values
128+
!> Array of eigenvalues
129129
complex(${rk}$), allocatable :: lambda(:)
130130

131131
!> Create
@@ -154,9 +154,9 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
154154
${rt}$, intent(inout), target :: a(:,:)
155155
!> Array of eigenvalues
156156
complex(${rk}$), intent(out) :: lambda(:)
157-
!> The columns of RIGHT contain the right eigenvectors of A
157+
!> [optional] RIGHT eigenvectors of A (as columns)
158158
complex(${rk}$), optional, intent(out), target :: right(:,:)
159-
!> The columns of LEFT contain the left eigenvectors of A
159+
!> [optional] LEFT eigenvectors of A (as columns)
160160
complex(${rk}$), optional, intent(out), target :: left(:,:)
161161
!> [optional] Can A data be overwritten and destroyed?
162162
logical(lk), optional, intent(in) :: overwrite_a
@@ -323,7 +323,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
323323
logical(lk), optional, intent(in) :: upper_a
324324
!> [optional] state return flag. On error if not requested, the code will stop
325325
type(linalg_state_type), intent(out) :: err
326-
!> Array of singular values
326+
!> Array of eigenvalues
327327
real(${rk}$), allocatable :: lambda(:)
328328

329329
${rt}$, pointer :: amat(:,:)
@@ -348,9 +348,9 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
348348
!! Return an array of eigenvalues of real symmetric / complex hermitian A
349349
!> Input matrix A[m,n]
350350
${rt}$, intent(in), target :: a(:,:)
351-
!> [optional] Should the upper/lower half of A be used? Default: lower
351+
!> [optional] Should the upper/lower half of A be used? Default: use lower
352352
logical(lk), optional, intent(in) :: upper_a
353-
!> Array of singular values
353+
!> Array of eigenvalues
354354
real(${rk}$), allocatable :: lambda(:)
355355

356356
${rt}$, pointer :: amat(:,:)
@@ -382,7 +382,7 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
382382
${rt}$, optional, intent(out), target :: vectors(:,:)
383383
!> [optional] Can A data be overwritten and destroyed?
384384
logical(lk), optional, intent(in) :: overwrite_a
385-
!> [optional] Should the upper/lower half of A be used? Default: lower
385+
!> [optional] Should the upper/lower half of A be used? Default: use lower
386386
logical(lk), optional, intent(in) :: upper_a
387387
!> [optional] state return flag. On error if not requested, the code will stop
388388
type(linalg_state_type), optional, intent(out) :: err

0 commit comments

Comments
 (0)