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))
811module stdlib_linalg
912 !!Provides a support for various linear algebra procedures
1013 !! ([Specification](../page/specs/stdlib_linalg.html))
@@ -832,12 +835,16 @@ module stdlib_linalg
832835 !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
833836 !!
834837 #:for rk,rt,ri in RC_KINDS_TYPES
835- #:if rk!="xdp"
836- module subroutine stdlib_linalg_eig_${ri}$(a,lambda,right,left,overwrite_a,err)
838+ #:for ep,ei in EIG_PROBLEM_LIST
839+ module subroutine stdlib_linalg_eig_${ep}$_${ ri}$(a#{if ei=='ggev'}#,b#{endif}# ,lambda,right,left,overwrite_a,err)
837840 !! Eigendecomposition of matrix A returning an array `lambda` of eigenvalues,
838841 !! and optionally right or left eigenvectors.
839842 !> Input matrix A[m,n]
840843 ${rt}$, intent(inout), target :: a(:,:)
844+ #:if ei=='ggev'
845+ !> Generalized problem matrix B[n,n]
846+ ${rt}$, intent(inout), target :: b(:,:)
847+ #:endif
841848 !> Array of eigenvalues
842849 complex(${rk}$), intent(out) :: lambda(:)
843850 !> The columns of RIGHT contain the right eigenvectors of A
@@ -848,17 +855,18 @@ module stdlib_linalg
848855 logical(lk), optional, intent(in) :: overwrite_a
849856 !> [optional] state return flag. On error if not requested, the code will stop
850857 type(linalg_state_type), optional, intent(out) :: err
851- end subroutine stdlib_linalg_eig_${ri}$
852- #:endif
853- #:endfor
854- #:for rk,rt,ri in REAL_KINDS_TYPES
855- #:if rk!="xdp"
856- module subroutine stdlib_linalg_real_eig_${ri}$(a,lambda,right,left,overwrite_a,err)
858+ end subroutine stdlib_linalg_eig_${ep}$_${ri}$
859+
860+ module subroutine stdlib_linalg_real_eig_${ep}$_${ri}$(a#{if ei=='ggev'}#,b#{endif}#,lambda,right,left,overwrite_a,err)
857861 !! Eigendecomposition of matrix A returning an array `lambda` of real eigenvalues,
858862 !! and optionally right or left eigenvectors. Returns an error if the eigenvalues had
859863 !! non-trivial imaginary parts.
860864 !> Input matrix A[m,n]
861- ${rt}$, intent(inout), target :: a(:,:)
865+ ${rt}$, intent(in), target :: a(:,:)
866+ #:if ei=='ggev'
867+ !> Generalized problem matrix B[n,n]
868+ ${rt}$, intent(inout), target :: b(:,:)
869+ #:endif
862870 !> Array of real eigenvalues
863871 real(${rk}$), intent(out) :: lambda(:)
864872 !> The columns of RIGHT contain the right eigenvectors of A
@@ -869,9 +877,9 @@ module stdlib_linalg
869877 logical(lk), optional, intent(in) :: overwrite_a
870878 !> [optional] state return flag. On error if not requested, the code will stop
871879 type(linalg_state_type), optional, intent(out) :: err
872- end subroutine stdlib_linalg_real_eig_${ri}$
873- #:endif
880+ end subroutine stdlib_linalg_real_eig_${ep}$_${ri}$
874881 #:endfor
882+ #:endfor
875883 end interface eig
876884
877885 ! Eigenvalues of a square matrix
@@ -895,25 +903,33 @@ module stdlib_linalg
895903 !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
896904 !!
897905 #:for rk,rt,ri in RC_KINDS_TYPES
898- #:if rk!="xdp"
899- module function stdlib_linalg_eigvals_${ri}$(a,err) result(lambda)
906+ #:for ep,ei in EIG_PROBLEM_LIST
907+ module function stdlib_linalg_eigvals_${ep}$_${ ri}$(a#{if ei=='ggev'}#,b#{endif}# ,err) result(lambda)
900908 !! Return an array of eigenvalues of matrix A.
901909 !> Input matrix A[m,n]
902- ${rt}$, intent(in), target :: a(:,:)
910+ ${rt}$, intent(in), dimension(:,:), target :: a
911+ #:if ei=='ggev'
912+ !> Generalized problem matrix B[n,n]
913+ ${rt}$, intent(inout), dimension(:,:), target :: b
914+ #:endif
903915 !> [optional] state return flag. On error if not requested, the code will stop
904916 type(linalg_state_type), intent(out) :: err
905917 !> Array of singular values
906918 complex(${rk}$), allocatable :: lambda(:)
907- end function stdlib_linalg_eigvals_${ri}$
919+ end function stdlib_linalg_eigvals_${ep}$_${ ri}$
908920
909- module function stdlib_linalg_eigvals_noerr_${ri}$(a) result(lambda)
921+ module function stdlib_linalg_eigvals_noerr_${ep}$_${ ri}$(a#{if ei=='ggev'}#,b#{endif}# ) result(lambda)
910922 !! Return an array of eigenvalues of matrix A.
911923 !> Input matrix A[m,n]
912- ${rt}$, intent(in), target :: a(:,:)
924+ ${rt}$, intent(in), dimension(:,:), target :: a
925+ #:if ei=='ggev'
926+ !> Generalized problem matrix B[n,n]
927+ ${rt}$, intent(inout), dimension(:,:), target :: b
928+ #:endif
913929 !> Array of singular values
914930 complex(${rk}$), allocatable :: lambda(:)
915- end function stdlib_linalg_eigvals_noerr_${ri}$
916- #:endif
931+ end function stdlib_linalg_eigvals_noerr_${ep}$_${ ri}$
932+ #:endfor
917933 #:endfor
918934 end interface eigvals
919935
@@ -942,7 +958,6 @@ module stdlib_linalg
942958 !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
943959 !!
944960 #:for rk,rt,ri in RC_KINDS_TYPES
945- #:if rk!="xdp"
946961 module subroutine stdlib_linalg_eigh_${ri}$(a,lambda,vectors,upper_a,overwrite_a,err)
947962 !! Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array `lambda`
948963 !! of eigenvalues, and optionally right or left eigenvectors.
@@ -959,7 +974,6 @@ module stdlib_linalg
959974 !> [optional] state return flag. On error if not requested, the code will stop
960975 type(linalg_state_type), optional, intent(out) :: err
961976 end subroutine stdlib_linalg_eigh_${ri}$
962- #:endif
963977 #:endfor
964978 end interface eigh
965979
@@ -987,7 +1001,6 @@ module stdlib_linalg
9871001 !!@note BLAS/LAPACK backends do not currently support extended precision (``xdp``).
9881002 !!
9891003 #:for rk,rt,ri in RC_KINDS_TYPES
990- #:if rk!="xdp"
9911004 module function stdlib_linalg_eigvalsh_${ri}$(a,upper_a,err) result(lambda)
9921005 !! Return an array of eigenvalues of real symmetric / complex hermitian A
9931006 !> Input matrix A[m,n]
@@ -1009,7 +1022,6 @@ module stdlib_linalg
10091022 !> Array of singular values
10101023 real(${rk}$), allocatable :: lambda(:)
10111024 end function stdlib_linalg_eigvalsh_noerr_${ri}$
1012- #:endif
10131025 #:endfor
10141026 end interface eigvalsh
10151027
0 commit comments