#:include "common.fypp" module stdlib_lapack_solve use stdlib_linalg_constants use stdlib_linalg_lapack_aux use stdlib_linalg_blas use stdlib_lapack_base implicit none interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slacn2( n, v, x, isgn, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) integer(${ik}$), intent(inout) :: isave(3_${ik}$) real(sp), intent(out) :: v(*) real(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_slacn2 pure module subroutine stdlib${ii}$_dlacn2( n, v, x, isgn, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) integer(${ik}$), intent(inout) :: isave(3_${ik}$) real(dp), intent(out) :: v(*) real(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_dlacn2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$lacn2( n, v, x, isgn, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(${rk}$), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) integer(${ik}$), intent(inout) :: isave(3_${ik}$) real(${rk}$), intent(out) :: v(*) real(${rk}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ri}$lacn2 #:endif #:endfor pure module subroutine stdlib${ii}$_clacn2( n, v, x, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: est integer(${ik}$), intent(inout) :: isave(3_${ik}$) complex(sp), intent(out) :: v(*) complex(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_clacn2 pure module subroutine stdlib${ii}$_zlacn2( n, v, x, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: est integer(${ik}$), intent(inout) :: isave(3_${ik}$) complex(dp), intent(out) :: v(*) complex(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_zlacn2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$lacn2( n, v, x, est, kase, isave ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(${ck}$), intent(inout) :: est integer(${ik}$), intent(inout) :: isave(3_${ik}$) complex(${ck}$), intent(out) :: v(*) complex(${ck}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ci}$lacn2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES module subroutine stdlib${ii}$_slacon( n, v, x, isgn, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) real(sp), intent(out) :: v(*) real(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_slacon module subroutine stdlib${ii}$_dlacon( n, v, x, isgn, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) real(dp), intent(out) :: v(*) real(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_dlacon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] module subroutine stdlib${ii}$_${ri}$lacon( n, v, x, isgn, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(${rk}$), intent(inout) :: est integer(${ik}$), intent(out) :: isgn(*) real(${rk}$), intent(out) :: v(*) real(${rk}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ri}$lacon #:endif #:endfor module subroutine stdlib${ii}$_clacon( n, v, x, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: est complex(sp), intent(out) :: v(n) complex(sp), intent(inout) :: x(n) end subroutine stdlib${ii}$_clacon module subroutine stdlib${ii}$_zlacon( n, v, x, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: est complex(dp), intent(out) :: v(n) complex(dp), intent(inout) :: x(n) end subroutine stdlib${ii}$_zlacon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] module subroutine stdlib${ii}$_${ci}$lacon( n, v, x, est, kase ) integer(${ik}$), intent(inout) :: kase integer(${ik}$), intent(in) :: n real(${ck}$), intent(inout) :: est complex(${ck}$), intent(out) :: v(n) complex(${ck}$), intent(inout) :: x(n) end subroutine stdlib${ii}$_${ci}$lacon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sla_lin_berr( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(sp), intent(in) :: ayb(n,nrhs) real(sp), intent(out) :: berr(nrhs) real(sp), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_sla_lin_berr pure module subroutine stdlib${ii}$_dla_lin_berr ( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(dp), intent(in) :: ayb(n,nrhs) real(dp), intent(out) :: berr(nrhs) real(dp), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_dla_lin_berr #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$la_lin_berr ( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(${rk}$), intent(in) :: ayb(n,nrhs) real(${rk}$), intent(out) :: berr(nrhs) real(${rk}$), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_${ri}$la_lin_berr #:endif #:endfor pure module subroutine stdlib${ii}$_cla_lin_berr( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(sp), intent(in) :: ayb(n,nrhs) real(sp), intent(out) :: berr(nrhs) complex(sp), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_cla_lin_berr pure module subroutine stdlib${ii}$_zla_lin_berr( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(dp), intent(in) :: ayb(n,nrhs) real(dp), intent(out) :: berr(nrhs) complex(dp), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_zla_lin_berr #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$la_lin_berr( n, nz, nrhs, res, ayb, berr ) integer(${ik}$), intent(in) :: n, nz, nrhs real(${ck}$), intent(in) :: ayb(n,nrhs) real(${ck}$), intent(out) :: berr(nrhs) complex(${ck}$), intent(in) :: res(n,nrhs) end subroutine stdlib${ii}$_${ci}$la_lin_berr #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES module subroutine stdlib${ii}$_strcon( norm, uplo, diag, n, a, lda, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: a(lda,*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_strcon module subroutine stdlib${ii}$_dtrcon( norm, uplo, diag, n, a, lda, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: a(lda,*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dtrcon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] module subroutine stdlib${ii}$_${ri}$trcon( norm, uplo, diag, n, a, lda, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$trcon #:endif #:endfor module subroutine stdlib${ii}$_ctrcon( norm, uplo, diag, n, a, lda, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: rcond real(sp), intent(out) :: rwork(*) complex(sp), intent(in) :: a(lda,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctrcon module subroutine stdlib${ii}$_ztrcon( norm, uplo, diag, n, a, lda, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: rcond real(dp), intent(out) :: rwork(*) complex(dp), intent(in) :: a(lda,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztrcon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] module subroutine stdlib${ii}$_${ci}$trcon( norm, uplo, diag, n, a, lda, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${ck}$), intent(out) :: rcond real(${ck}$), intent(out) :: rwork(*) complex(${ck}$), intent(in) :: a(lda,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$trcon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_strtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs real(sp), intent(in) :: a(lda,*) real(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_strtrs pure module subroutine stdlib${ii}$_dtrtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs real(dp), intent(in) :: a(lda,*) real(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_dtrtrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$trtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ri}$trtrs #:endif #:endfor pure module subroutine stdlib${ii}$_ctrtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs complex(sp), intent(in) :: a(lda,*) complex(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ctrtrs pure module subroutine stdlib${ii}$_ztrtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs complex(dp), intent(in) :: a(lda,*) complex(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ztrtrs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$trtrs( uplo, trans, diag, n, nrhs, a, lda, b, ldb,info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs complex(${ck}$), intent(in) :: a(lda,*) complex(${ck}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ci}$trtrs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slatrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: scale real(sp), intent(in) :: a(lda,*) real(sp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_slatrs pure module subroutine stdlib${ii}$_dlatrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: scale real(dp), intent(in) :: a(lda,*) real(dp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_dlatrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$latrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(out) :: scale real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_${ri}$latrs #:endif #:endfor pure module subroutine stdlib${ii}$_clatrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: scale real(sp), intent(inout) :: cnorm(*) complex(sp), intent(in) :: a(lda,*) complex(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_clatrs pure module subroutine stdlib${ii}$_zlatrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: scale real(dp), intent(inout) :: cnorm(*) complex(dp), intent(in) :: a(lda,*) complex(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_zlatrs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$latrs( uplo, trans, diag, normin, n, a, lda, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${ck}$), intent(out) :: scale real(${ck}$), intent(inout) :: cnorm(*) complex(${ck}$), intent(in) :: a(lda,*) complex(${ck}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ci}$latrs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_strtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_strtri pure module subroutine stdlib${ii}$_dtrtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dtrtri #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$trtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$trtri #:endif #:endfor pure module subroutine stdlib${ii}$_ctrtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_ctrtri pure module subroutine stdlib${ii}$_ztrtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_ztrtri #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$trtri( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$trtri #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_strti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_strti2 pure module subroutine stdlib${ii}$_dtrti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dtrti2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$trti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$trti2 #:endif #:endfor pure module subroutine stdlib${ii}$_ctrti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_ctrti2 pure module subroutine stdlib${ii}$_ztrti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_ztrti2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$trti2( uplo, diag, n, a, lda, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$trti2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_strrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) real(sp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_strrfs pure module subroutine stdlib${ii}$_dtrrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) real(dp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_dtrrfs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$trrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) real(${rk}$), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_${ri}$trrfs #:endif #:endfor pure module subroutine stdlib${ii}$_ctrrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs real(sp), intent(out) :: berr(*), ferr(*), rwork(*) complex(sp), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctrrfs pure module subroutine stdlib${ii}$_ztrrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs real(dp), intent(out) :: berr(*), ferr(*), rwork(*) complex(dp), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztrrfs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$trrfs( uplo, trans, diag, n, nrhs, a, lda, b, ldb, x,ldx, ferr, berr,& work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, ldx, n, nrhs real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*) complex(${ck}$), intent(in) :: a(lda,*), b(ldb,*), x(ldx,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$trrfs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_slauum pure module subroutine stdlib${ii}$_dlauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dlauum #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$lauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$lauum #:endif #:endfor pure module subroutine stdlib${ii}$_clauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_clauum pure module subroutine stdlib${ii}$_zlauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zlauum #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$lauum( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$lauum #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_slauu2 pure module subroutine stdlib${ii}$_dlauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dlauu2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$lauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$lauu2 #:endif #:endfor pure module subroutine stdlib${ii}$_clauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_clauu2 pure module subroutine stdlib${ii}$_zlauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zlauu2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$lauu2( uplo, n, a, lda, info ) character, intent(in) :: uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$lauu2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES module subroutine stdlib${ii}$_stpcon( norm, uplo, diag, n, ap, rcond, work, iwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: ap(*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_stpcon module subroutine stdlib${ii}$_dtpcon( norm, uplo, diag, n, ap, rcond, work, iwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: ap(*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dtpcon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] module subroutine stdlib${ii}$_${ri}$tpcon( norm, uplo, diag, n, ap, rcond, work, iwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${rk}$), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: ap(*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$tpcon #:endif #:endfor module subroutine stdlib${ii}$_ctpcon( norm, uplo, diag, n, ap, rcond, work, rwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(out) :: rcond real(sp), intent(out) :: rwork(*) complex(sp), intent(in) :: ap(*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctpcon module subroutine stdlib${ii}$_ztpcon( norm, uplo, diag, n, ap, rcond, work, rwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(out) :: rcond real(dp), intent(out) :: rwork(*) complex(dp), intent(in) :: ap(*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztpcon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] module subroutine stdlib${ii}$_${ci}$tpcon( norm, uplo, diag, n, ap, rcond, work, rwork,info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${ck}$), intent(out) :: rcond real(${ck}$), intent(out) :: rwork(*) complex(${ck}$), intent(in) :: ap(*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$tpcon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs real(sp), intent(in) :: ap(*) real(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_stptrs pure module subroutine stdlib${ii}$_dtptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs real(dp), intent(in) :: ap(*) real(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_dtptrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs real(${rk}$), intent(in) :: ap(*) real(${rk}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ri}$tptrs #:endif #:endfor pure module subroutine stdlib${ii}$_ctptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs complex(sp), intent(in) :: ap(*) complex(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ctptrs pure module subroutine stdlib${ii}$_ztptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs complex(dp), intent(in) :: ap(*) complex(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ztptrs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tptrs( uplo, trans, diag, n, nrhs, ap, b, ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, n, nrhs complex(${ck}$), intent(in) :: ap(*) complex(${ck}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ci}$tptrs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slatps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(out) :: scale real(sp), intent(in) :: ap(*) real(sp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_slatps pure module subroutine stdlib${ii}$_dlatps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(out) :: scale real(dp), intent(in) :: ap(*) real(dp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_dlatps #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$latps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${rk}$), intent(out) :: scale real(${rk}$), intent(in) :: ap(*) real(${rk}$), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_${ri}$latps #:endif #:endfor pure module subroutine stdlib${ii}$_clatps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(out) :: scale real(sp), intent(inout) :: cnorm(*) complex(sp), intent(in) :: ap(*) complex(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_clatps pure module subroutine stdlib${ii}$_zlatps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(out) :: scale real(dp), intent(inout) :: cnorm(*) complex(dp), intent(in) :: ap(*) complex(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_zlatps #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$latps( uplo, trans, diag, normin, n, ap, x, scale,cnorm, info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${ck}$), intent(out) :: scale real(${ck}$), intent(inout) :: cnorm(*) complex(${ck}$), intent(in) :: ap(*) complex(${ck}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ci}$latps #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: ap(*) end subroutine stdlib${ii}$_stptri pure module subroutine stdlib${ii}$_dtptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: ap(*) end subroutine stdlib${ii}$_dtptri #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${rk}$), intent(inout) :: ap(*) end subroutine stdlib${ii}$_${ri}$tptri #:endif #:endfor pure module subroutine stdlib${ii}$_ctptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(sp), intent(inout) :: ap(*) end subroutine stdlib${ii}$_ctptri pure module subroutine stdlib${ii}$_ztptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(dp), intent(inout) :: ap(*) end subroutine stdlib${ii}$_ztptri #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tptri( uplo, diag, n, ap, info ) character, intent(in) :: diag, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(${ck}$), intent(inout) :: ap(*) end subroutine stdlib${ii}$_${ci}$tptri #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: ap(*), b(ldb,*), x(ldx,*) real(sp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_stprfs pure module subroutine stdlib${ii}$_dtprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: ap(*), b(ldb,*), x(ldx,*) real(dp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_dtprfs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: ap(*), b(ldb,*), x(ldx,*) real(${rk}$), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_${ri}$tprfs #:endif #:endfor pure module subroutine stdlib${ii}$_ctprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs real(sp), intent(out) :: berr(*), ferr(*), rwork(*) complex(sp), intent(in) :: ap(*), b(ldb,*), x(ldx,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctprfs pure module subroutine stdlib${ii}$_ztprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs real(dp), intent(out) :: berr(*), ferr(*), rwork(*) complex(dp), intent(in) :: ap(*), b(ldb,*), x(ldx,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztprfs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tprfs( uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx,ferr, berr, & work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*) complex(${ck}$), intent(in) :: ap(*), b(ldb,*), x(ldx,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$tprfs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(sp), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_stftri pure module subroutine stdlib${ii}$_dtftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(dp), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_dtftri #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n real(${rk}$), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_${ri}$tftri #:endif #:endfor pure module subroutine stdlib${ii}$_ctftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(sp), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_ctftri pure module subroutine stdlib${ii}$_ztftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(dp), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_ztftri #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tftri( transr, uplo, diag, n, a, info ) character, intent(in) :: transr, uplo, diag integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: n complex(${ck}$), intent(inout) :: a(0_${ik}$:*) end subroutine stdlib${ii}$_${ci}$tftri #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES module subroutine stdlib${ii}$_stbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(sp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: ab(ldab,*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_stbcon module subroutine stdlib${ii}$_dtbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(dp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: ab(ldab,*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dtbcon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] module subroutine stdlib${ii}$_${ri}$tbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,iwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(${rk}$), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: ab(ldab,*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$tbcon #:endif #:endfor module subroutine stdlib${ii}$_ctbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(sp), intent(out) :: rcond real(sp), intent(out) :: rwork(*) complex(sp), intent(in) :: ab(ldab,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctbcon module subroutine stdlib${ii}$_ztbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(dp), intent(out) :: rcond real(dp), intent(out) :: rwork(*) complex(dp), intent(in) :: ab(ldab,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztbcon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] module subroutine stdlib${ii}$_${ci}$tbcon( norm, uplo, diag, n, kd, ab, ldab, rcond, work,rwork, info ) character, intent(in) :: diag, norm, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(${ck}$), intent(out) :: rcond real(${ck}$), intent(out) :: rwork(*) complex(${ck}$), intent(in) :: ab(ldab,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$tbcon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs real(sp), intent(in) :: ab(ldab,*) real(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_stbtrs pure module subroutine stdlib${ii}$_dtbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs real(dp), intent(in) :: ab(ldab,*) real(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_dtbtrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs real(${rk}$), intent(in) :: ab(ldab,*) real(${rk}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ri}$tbtrs #:endif #:endfor pure module subroutine stdlib${ii}$_ctbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs complex(sp), intent(in) :: ab(ldab,*) complex(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ctbtrs pure module subroutine stdlib${ii}$_ztbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs complex(dp), intent(in) :: ab(ldab,*) complex(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_ztbtrs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tbtrs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs complex(${ck}$), intent(in) :: ab(ldab,*) complex(${ck}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ci}$tbtrs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slatbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(sp), intent(out) :: scale real(sp), intent(in) :: ab(ldab,*) real(sp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_slatbs pure module subroutine stdlib${ii}$_dlatbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(dp), intent(out) :: scale real(dp), intent(in) :: ab(ldab,*) real(dp), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_dlatbs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$latbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(${rk}$), intent(out) :: scale real(${rk}$), intent(in) :: ab(ldab,*) real(${rk}$), intent(inout) :: cnorm(*), x(*) end subroutine stdlib${ii}$_${ri}$latbs #:endif #:endfor pure module subroutine stdlib${ii}$_clatbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(sp), intent(out) :: scale real(sp), intent(inout) :: cnorm(*) complex(sp), intent(in) :: ab(ldab,*) complex(sp), intent(inout) :: x(*) end subroutine stdlib${ii}$_clatbs pure module subroutine stdlib${ii}$_zlatbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(dp), intent(out) :: scale real(dp), intent(inout) :: cnorm(*) complex(dp), intent(in) :: ab(ldab,*) complex(dp), intent(inout) :: x(*) end subroutine stdlib${ii}$_zlatbs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$latbs( uplo, trans, diag, normin, n, kd, ab, ldab, x,scale, cnorm, & info ) character, intent(in) :: diag, normin, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, n real(${ck}$), intent(out) :: scale real(${ck}$), intent(inout) :: cnorm(*) complex(${ck}$), intent(in) :: ab(ldab,*) complex(${ck}$), intent(inout) :: x(*) end subroutine stdlib${ii}$_${ci}$latbs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_stbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) real(sp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_stbrfs pure module subroutine stdlib${ii}$_dtbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) real(dp), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_dtbrfs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$tbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, iwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) real(${rk}$), intent(out) :: berr(*), ferr(*), work(*) end subroutine stdlib${ii}$_${ri}$tbrfs #:endif #:endfor pure module subroutine stdlib${ii}$_ctbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs real(sp), intent(out) :: berr(*), ferr(*), rwork(*) complex(sp), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_ctbrfs pure module subroutine stdlib${ii}$_ztbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs real(dp), intent(out) :: berr(*), ferr(*), rwork(*) complex(dp), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_ztbrfs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$tbrfs( uplo, trans, diag, n, kd, nrhs, ab, ldab, b,ldb, x, ldx, ferr,& berr, work, rwork, info ) character, intent(in) :: diag, trans, uplo integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kd, ldab, ldb, ldx, n, nrhs real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*) complex(${ck}$), intent(in) :: ab(ldab,*), b(ldb,*), x(ldx,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$tbrfs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgecon( norm, n, a, lda, anorm, rcond, work, iwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(in) :: anorm real(sp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(inout) :: a(lda,*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_sgecon pure module subroutine stdlib${ii}$_dgecon( norm, n, a, lda, anorm, rcond, work, iwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(in) :: anorm real(dp), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(inout) :: a(lda,*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dgecon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gecon( norm, n, a, lda, anorm, rcond, work, iwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(in) :: anorm real(${rk}$), intent(out) :: rcond integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(inout) :: a(lda,*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$gecon #:endif #:endfor pure module subroutine stdlib${ii}$_cgecon( norm, n, a, lda, anorm, rcond, work, rwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(sp), intent(in) :: anorm real(sp), intent(out) :: rcond real(sp), intent(out) :: rwork(*) complex(sp), intent(inout) :: a(lda,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_cgecon pure module subroutine stdlib${ii}$_zgecon( norm, n, a, lda, anorm, rcond, work, rwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(dp), intent(in) :: anorm real(dp), intent(out) :: rcond real(dp), intent(out) :: rwork(*) complex(dp), intent(inout) :: a(lda,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_zgecon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gecon( norm, n, a, lda, anorm, rcond, work, rwork,info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n real(${ck}$), intent(in) :: anorm real(${ck}$), intent(out) :: rcond real(${ck}$), intent(out) :: rwork(*) complex(${ck}$), intent(inout) :: a(lda,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$gecon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgetrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_sgetrf pure module subroutine stdlib${ii}$_dgetrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dgetrf #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$getrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$getrf #:endif #:endfor pure module subroutine stdlib${ii}$_cgetrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_cgetrf pure module subroutine stdlib${ii}$_zgetrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zgetrf #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$getrf( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$getrf #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure recursive module subroutine stdlib${ii}$_sgetrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_sgetrf2 pure recursive module subroutine stdlib${ii}$_dgetrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dgetrf2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure recursive module subroutine stdlib${ii}$_${ri}$getrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$getrf2 #:endif #:endfor pure recursive module subroutine stdlib${ii}$_cgetrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_cgetrf2 pure recursive module subroutine stdlib${ii}$_zgetrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zgetrf2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure recursive module subroutine stdlib${ii}$_${ci}$getrf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$getrf2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgetf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_sgetf2 pure module subroutine stdlib${ii}$_dgetf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dgetf2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$getf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$getf2 #:endif #:endfor pure module subroutine stdlib${ii}$_cgetf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_cgetf2 pure module subroutine stdlib${ii}$_zgetf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zgetf2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$getf2( m, n, a, lda, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$getf2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgetrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(in) :: a(lda,*) real(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_sgetrs pure module subroutine stdlib${ii}$_dgetrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(in) :: a(lda,*) real(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_dgetrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$getrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ri}$getrs #:endif #:endfor pure module subroutine stdlib${ii}$_cgetrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) complex(sp), intent(in) :: a(lda,*) complex(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_cgetrs pure module subroutine stdlib${ii}$_zgetrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) complex(dp), intent(in) :: a(lda,*) complex(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_zgetrs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$getrs( trans, n, nrhs, a, lda, ipiv, b, ldb, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) complex(${ck}$), intent(in) :: a(lda,*) complex(${ck}$), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_${ci}$getrs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgetri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(inout) :: a(lda,*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_sgetri pure module subroutine stdlib${ii}$_dgetri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(inout) :: a(lda,*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dgetri #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$getri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) real(${rk}$), intent(inout) :: a(lda,*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$getri #:endif #:endfor pure module subroutine stdlib${ii}$_cgetri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) complex(sp), intent(inout) :: a(lda,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_cgetri pure module subroutine stdlib${ii}$_zgetri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) complex(dp), intent(inout) :: a(lda,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_zgetri #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$getri( n, a, lda, ipiv, work, lwork, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, lwork, n integer(${ik}$), intent(in) :: ipiv(*) complex(${ck}$), intent(inout) :: a(lda,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$getri #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, iwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) real(sp), intent(out) :: berr(*), ferr(*), work(*) real(sp), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_sgerfs pure module subroutine stdlib${ii}$_dgerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, iwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) real(dp), intent(out) :: berr(*), ferr(*), work(*) real(dp), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_dgerfs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, iwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) real(${rk}$), intent(out) :: berr(*), ferr(*), work(*) real(${rk}$), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_${ri}$gerfs #:endif #:endfor pure module subroutine stdlib${ii}$_cgerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, rwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(out) :: berr(*), ferr(*), rwork(*) complex(sp), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) complex(sp), intent(out) :: work(*) complex(sp), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_cgerfs pure module subroutine stdlib${ii}$_zgerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, rwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(out) :: berr(*), ferr(*), rwork(*) complex(dp), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) complex(dp), intent(out) :: work(*) complex(dp), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_zgerfs #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gerfs( trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, & berr, work, rwork, info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*) complex(${ck}$), intent(in) :: a(lda,*), af(ldaf,*), b(ldb,*) complex(${ck}$), intent(out) :: work(*) complex(${ck}$), intent(inout) :: x(ldx,*) end subroutine stdlib${ii}$_${ci}$gerfs #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgeequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(out) :: amax, colcnd, rowcnd real(sp), intent(in) :: a(lda,*) real(sp), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_sgeequ pure module subroutine stdlib${ii}$_dgeequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(out) :: amax, colcnd, rowcnd real(dp), intent(in) :: a(lda,*) real(dp), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_dgeequ #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$geequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(${rk}$), intent(out) :: amax, colcnd, rowcnd real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_${ri}$geequ #:endif #:endfor pure module subroutine stdlib${ii}$_cgeequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(out) :: amax, colcnd, rowcnd real(sp), intent(out) :: c(*), r(*) complex(sp), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_cgeequ pure module subroutine stdlib${ii}$_zgeequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(out) :: amax, colcnd, rowcnd real(dp), intent(out) :: c(*), r(*) complex(dp), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_zgeequ #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$geequ( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(${ck}$), intent(out) :: amax, colcnd, rowcnd real(${ck}$), intent(out) :: c(*), r(*) complex(${ck}$), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$geequ #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgeequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(out) :: amax, colcnd, rowcnd real(sp), intent(in) :: a(lda,*) real(sp), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_sgeequb pure module subroutine stdlib${ii}$_dgeequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(out) :: amax, colcnd, rowcnd real(dp), intent(in) :: a(lda,*) real(dp), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_dgeequb #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$geequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(${rk}$), intent(out) :: amax, colcnd, rowcnd real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(out) :: c(*), r(*) end subroutine stdlib${ii}$_${ri}$geequb #:endif #:endfor pure module subroutine stdlib${ii}$_cgeequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(out) :: amax, colcnd, rowcnd real(sp), intent(out) :: c(*), r(*) complex(sp), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_cgeequb pure module subroutine stdlib${ii}$_zgeequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(out) :: amax, colcnd, rowcnd real(dp), intent(out) :: c(*), r(*) complex(dp), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_zgeequb #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$geequb( m, n, a, lda, r, c, rowcnd, colcnd, amax,info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, m, n real(${ck}$), intent(out) :: amax, colcnd, rowcnd real(${ck}$), intent(out) :: c(*), r(*) complex(${ck}$), intent(in) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$geequb #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slaqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(in) :: amax, colcnd, rowcnd real(sp), intent(inout) :: a(lda,*) real(sp), intent(in) :: c(*), r(*) end subroutine stdlib${ii}$_slaqge pure module subroutine stdlib${ii}$_dlaqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(in) :: amax, colcnd, rowcnd real(dp), intent(inout) :: a(lda,*) real(dp), intent(in) :: c(*), r(*) end subroutine stdlib${ii}$_dlaqge #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$laqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(${rk}$), intent(in) :: amax, colcnd, rowcnd real(${rk}$), intent(inout) :: a(lda,*) real(${rk}$), intent(in) :: c(*), r(*) end subroutine stdlib${ii}$_${ri}$laqge #:endif #:endfor pure module subroutine stdlib${ii}$_claqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(sp), intent(in) :: amax, colcnd, rowcnd real(sp), intent(in) :: c(*), r(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_claqge pure module subroutine stdlib${ii}$_zlaqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(dp), intent(in) :: amax, colcnd, rowcnd real(dp), intent(in) :: c(*), r(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zlaqge #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$laqge( m, n, a, lda, r, c, rowcnd, colcnd, amax,equed ) character, intent(out) :: equed integer(${ik}$), intent(in) :: lda, m, n real(${ck}$), intent(in) :: amax, colcnd, rowcnd real(${ck}$), intent(in) :: c(*), r(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$laqge #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slaswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_slaswp pure module subroutine stdlib${ii}$_dlaswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dlaswp #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$laswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$laswp #:endif #:endfor pure module subroutine stdlib${ii}$_claswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_claswp pure module subroutine stdlib${ii}$_zlaswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zlaswp #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$laswp( n, a, lda, k1, k2, ipiv, incx ) integer(${ik}$), intent(in) :: incx, k1, k2, lda, n integer(${ik}$), intent(in) :: ipiv(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$laswp #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgetc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) real(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_sgetc2 pure module subroutine stdlib${ii}$_dgetc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) real(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_dgetc2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$getc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) real(${rk}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ri}$getc2 #:endif #:endfor pure module subroutine stdlib${ii}$_cgetc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) complex(sp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_cgetc2 pure module subroutine stdlib${ii}$_zgetc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) complex(dp), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_zgetc2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$getc2( n, a, lda, ipiv, jpiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: lda, n integer(${ik}$), intent(out) :: ipiv(*), jpiv(*) complex(${ck}$), intent(inout) :: a(lda,*) end subroutine stdlib${ii}$_${ci}$getc2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(sp), intent(in) :: a(lda,*) real(sp), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_sgesc2 pure module subroutine stdlib${ii}$_dgesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(dp), intent(in) :: a(lda,*) real(dp), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_dgesc2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(${rk}$), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(${rk}$), intent(in) :: a(lda,*) real(${rk}$), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_${ri}$gesc2 #:endif #:endfor pure module subroutine stdlib${ii}$_cgesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(sp), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(sp), intent(in) :: a(lda,*) complex(sp), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_cgesc2 pure module subroutine stdlib${ii}$_zgesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(dp), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(dp), intent(in) :: a(lda,*) complex(dp), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_zgesc2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gesc2( n, a, lda, rhs, ipiv, jpiv, scale ) integer(${ik}$), intent(in) :: lda, n real(${ck}$), intent(out) :: scale integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(${ck}$), intent(in) :: a(lda,*) complex(${ck}$), intent(inout) :: rhs(*) end subroutine stdlib${ii}$_${ci}$gesc2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_slatdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(sp), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(sp), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_slatdf pure module subroutine stdlib${ii}$_dlatdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(dp), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(dp), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_dlatdf #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$latdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(${rk}$), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) real(${rk}$), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_${ri}$latdf #:endif #:endfor pure module subroutine stdlib${ii}$_clatdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(sp), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(sp), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_clatdf pure module subroutine stdlib${ii}$_zlatdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(dp), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(dp), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_zlatdf #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$latdf( ijob, n, z, ldz, rhs, rdsum, rdscal, ipiv,jpiv ) integer(${ik}$), intent(in) :: ijob, ldz, n real(${ck}$), intent(inout) :: rdscal, rdsum integer(${ik}$), intent(in) :: ipiv(*), jpiv(*) complex(${ck}$), intent(inout) :: rhs(*), z(ldz,*) end subroutine stdlib${ii}$_${ci}$latdf #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES real(sp) module function stdlib${ii}$_sla_gercond( trans, n, a, lda, af, ldaf, ipiv,cmode, c, info, work, & iwork ) character, intent(in) :: trans integer(${ik}$), intent(in) :: n, lda, ldaf, cmode integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: a(lda,*), af(ldaf,*), c(*) real(sp), intent(out) :: work(*) end function stdlib${ii}$_sla_gercond real(dp) module function stdlib${ii}$_dla_gercond( trans, n, a, lda, af,ldaf, ipiv, cmode, c,info, work, & iwork ) character, intent(in) :: trans integer(${ik}$), intent(in) :: n, lda, ldaf, cmode integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: a(lda,*), af(ldaf,*), c(*) real(dp), intent(out) :: work(*) end function stdlib${ii}$_dla_gercond #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] real(${rk}$) module function stdlib${ii}$_${ri}$la_gercond( trans, n, a, lda, af,ldaf, ipiv, cmode, c,info, work, & iwork ) character, intent(in) :: trans integer(${ik}$), intent(in) :: n, lda, ldaf, cmode integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: a(lda,*), af(ldaf,*), c(*) real(${rk}$), intent(out) :: work(*) end function stdlib${ii}$_${ri}$la_gercond #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, iwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(sp), intent(in) :: anorm real(sp), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(sp), intent(in) :: ab(ldab,*) real(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_sgbcon pure module subroutine stdlib${ii}$_dgbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, iwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(dp), intent(in) :: anorm real(dp), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(dp), intent(in) :: ab(ldab,*) real(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_dgbcon #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, iwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(${rk}$), intent(in) :: anorm real(${rk}$), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) integer(${ik}$), intent(out) :: iwork(*) real(${rk}$), intent(in) :: ab(ldab,*) real(${rk}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ri}$gbcon #:endif #:endfor pure module subroutine stdlib${ii}$_cgbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, rwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(sp), intent(in) :: anorm real(sp), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(out) :: rwork(*) complex(sp), intent(in) :: ab(ldab,*) complex(sp), intent(out) :: work(*) end subroutine stdlib${ii}$_cgbcon pure module subroutine stdlib${ii}$_zgbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, rwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(dp), intent(in) :: anorm real(dp), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(out) :: rwork(*) complex(dp), intent(in) :: ab(ldab,*) complex(dp), intent(out) :: work(*) end subroutine stdlib${ii}$_zgbcon #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gbcon( norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond,work, rwork, & info ) character, intent(in) :: norm integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, n real(${ck}$), intent(in) :: anorm real(${ck}$), intent(out) :: rcond integer(${ik}$), intent(in) :: ipiv(*) real(${ck}$), intent(out) :: rwork(*) complex(${ck}$), intent(in) :: ab(ldab,*) complex(${ck}$), intent(out) :: work(*) end subroutine stdlib${ii}$_${ci}$gbcon #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(sp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_sgbtrf pure module subroutine stdlib${ii}$_dgbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(dp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_dgbtrf #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(${rk}$), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_${ri}$gbtrf #:endif #:endfor pure module subroutine stdlib${ii}$_cgbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(sp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_cgbtrf pure module subroutine stdlib${ii}$_zgbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(dp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_zgbtrf #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gbtrf( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(${ck}$), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_${ci}$gbtrf #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(sp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_sgbtf2 pure module subroutine stdlib${ii}$_dgbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(dp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_dgbtf2 #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) real(${rk}$), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_${ri}$gbtf2 #:endif #:endfor pure module subroutine stdlib${ii}$_cgbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(sp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_cgbtf2 pure module subroutine stdlib${ii}$_zgbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(dp), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_zgbtf2 #:for ck,ct,ci in CMPLX_KINDS_TYPES #:if not ck in ["sp","dp"] pure module subroutine stdlib${ii}$_${ci}$gbtf2( m, n, kl, ku, ab, ldab, ipiv, info ) integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, m, n integer(${ik}$), intent(out) :: ipiv(*) complex(${ck}$), intent(inout) :: ab(ldab,*) end subroutine stdlib${ii}$_${ci}$gbtf2 #:endif #:endfor #:endfor end interface interface #:for ik,it,ii in LINALG_INT_KINDS_TYPES pure module subroutine stdlib${ii}$_sgbtrs( trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb,info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(sp), intent(in) :: ab(ldab,*) real(sp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_sgbtrs pure module subroutine stdlib${ii}$_dgbtrs( trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb,info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(dp), intent(in) :: ab(ldab,*) real(dp), intent(inout) :: b(ldb,*) end subroutine stdlib${ii}$_dgbtrs #:for rk,rt,ri in REAL_KINDS_TYPES #:if not rk in ["sp","dp"] pure module subroutine stdlib${ii}$_${ri}$gbtrs( trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb,info ) character, intent(in) :: trans integer(${ik}$), intent(out) :: info integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs integer(${ik}$), intent(in) :: ipiv(*) real(${rk}$), intent(in) :: ab(ldab,*) real(${rk}$), intent