stdlib_lapack_solve.fypp Source File


Source Code

#: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(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$gbtrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgbtrs( 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(*)
           complex(sp), intent(in) :: ab(ldab,*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_cgbtrs

     pure module subroutine stdlib${ii}$_zgbtrs( 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(*)
           complex(dp), intent(in) :: ab(ldab,*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zgbtrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$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(*)
           complex(${ck}$), intent(in) :: ab(ldab,*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$gbtrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_sgbrfs

     pure module subroutine stdlib${ii}$_dgbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dgbrfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$gbrfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_cgbrfs

     pure module subroutine stdlib${ii}$_zgbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zgbrfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gbrfs( trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$gbrfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(out) :: amax, colcnd, rowcnd
           real(sp), intent(in) :: ab(ldab,*)
           real(sp), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_sgbequ

     pure module subroutine stdlib${ii}$_dgbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(out) :: amax, colcnd, rowcnd
           real(dp), intent(in) :: ab(ldab,*)
           real(dp), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_dgbequ

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${rk}$), intent(out) :: amax, colcnd, rowcnd
           real(${rk}$), intent(in) :: ab(ldab,*)
           real(${rk}$), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_${ri}$gbequ

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(out) :: amax, colcnd, rowcnd
           real(sp), intent(out) :: c(*), r(*)
           complex(sp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_cgbequ

     pure module subroutine stdlib${ii}$_zgbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(out) :: amax, colcnd, rowcnd
           real(dp), intent(out) :: c(*), r(*)
           complex(dp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zgbequ

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gbequ( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${ck}$), intent(out) :: amax, colcnd, rowcnd
           real(${ck}$), intent(out) :: c(*), r(*)
           complex(${ck}$), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$gbequ

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(out) :: amax, colcnd, rowcnd
           real(sp), intent(in) :: ab(ldab,*)
           real(sp), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_sgbequb

     pure module subroutine stdlib${ii}$_dgbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(out) :: amax, colcnd, rowcnd
           real(dp), intent(in) :: ab(ldab,*)
           real(dp), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_dgbequb

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${rk}$), intent(out) :: amax, colcnd, rowcnd
           real(${rk}$), intent(in) :: ab(ldab,*)
           real(${rk}$), intent(out) :: c(*), r(*)
     end subroutine stdlib${ii}$_${ri}$gbequb

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(out) :: amax, colcnd, rowcnd
           real(sp), intent(out) :: c(*), r(*)
           complex(sp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_cgbequb

     pure module subroutine stdlib${ii}$_zgbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(out) :: amax, colcnd, rowcnd
           real(dp), intent(out) :: c(*), r(*)
           complex(dp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zgbequb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gbequb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${ck}$), intent(out) :: amax, colcnd, rowcnd
           real(${ck}$), intent(out) :: c(*), r(*)
           complex(${ck}$), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$gbequb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slaqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(in) :: amax, colcnd, rowcnd
           real(sp), intent(inout) :: ab(ldab,*)
           real(sp), intent(in) :: c(*), r(*)
     end subroutine stdlib${ii}$_slaqgb

     pure module subroutine stdlib${ii}$_dlaqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(in) :: amax, colcnd, rowcnd
           real(dp), intent(inout) :: ab(ldab,*)
           real(dp), intent(in) :: c(*), r(*)
     end subroutine stdlib${ii}$_dlaqgb

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$laqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${rk}$), intent(in) :: amax, colcnd, rowcnd
           real(${rk}$), intent(inout) :: ab(ldab,*)
           real(${rk}$), intent(in) :: c(*), r(*)
     end subroutine stdlib${ii}$_${ri}$laqgb

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_claqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(sp), intent(in) :: amax, colcnd, rowcnd
           real(sp), intent(in) :: c(*), r(*)
           complex(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_claqgb

     pure module subroutine stdlib${ii}$_zlaqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(dp), intent(in) :: amax, colcnd, rowcnd
           real(dp), intent(in) :: c(*), r(*)
           complex(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zlaqgb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqgb( m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd,amax, equed )
               
           character, intent(out) :: equed
           integer(${ik}$), intent(in) :: kl, ku, ldab, m, n
           real(${ck}$), intent(in) :: amax, colcnd, rowcnd
           real(${ck}$), intent(in) :: c(*), r(*)
           complex(${ck}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$laqgb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     real(sp) module function stdlib${ii}$_sla_gbrcond( trans, n, kl, ku, ab, ldab, afb, ldafb,ipiv, cmode, c, &
               info, work, iwork )
           character, intent(in) :: trans
           integer(${ik}$), intent(in) :: n, ldab, ldafb, kl, ku, cmode
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: iwork(*)
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(in) :: ab(ldab,*), afb(ldafb,*), c(*)
           real(sp), intent(out) :: work(*)
     end function stdlib${ii}$_sla_gbrcond

     real(dp) module function stdlib${ii}$_dla_gbrcond( trans, n, kl, ku, ab, ldab,afb, ldafb, ipiv, cmode, c,&
               info, work, iwork )
           character, intent(in) :: trans
           integer(${ik}$), intent(in) :: n, ldab, ldafb, kl, ku, cmode
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: iwork(*)
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(in) :: ab(ldab,*), afb(ldafb,*), c(*)
           real(dp), intent(out) :: work(*)
     end function stdlib${ii}$_dla_gbrcond

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     real(${rk}$) module function stdlib${ii}$_${ri}$la_gbrcond( trans, n, kl, ku, ab, ldab,afb, ldafb, ipiv, cmode, c,&
               info, work, iwork )
           character, intent(in) :: trans
           integer(${ik}$), intent(in) :: n, ldab, ldafb, kl, ku, cmode
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: iwork(*)
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(in) :: ab(ldab,*), afb(ldafb,*), c(*)
           real(${rk}$), intent(out) :: work(*)
     end function stdlib${ii}$_${ri}$la_gbrcond

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure real(sp) module function stdlib${ii}$_sla_gbrpvgrw( n, kl, ku, ncols, ab, ldab, afb,ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           real(sp), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_sla_gbrpvgrw

     pure real(dp) module function stdlib${ii}$_dla_gbrpvgrw( n, kl, ku, ncols, ab,ldab, afb, ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           real(dp), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_dla_gbrpvgrw

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure real(${rk}$) module function stdlib${ii}$_${ri}$la_gbrpvgrw( n, kl, ku, ncols, ab,ldab, afb, ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           real(${rk}$), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_${ri}$la_gbrpvgrw

#:endif
#:endfor

     pure real(sp) module function stdlib${ii}$_cla_gbrpvgrw( n, kl, ku, ncols, ab, ldab, afb,ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           complex(sp), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_cla_gbrpvgrw

     pure real(dp) module function stdlib${ii}$_zla_gbrpvgrw( n, kl, ku, ncols, ab,ldab, afb, ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           complex(dp), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_zla_gbrpvgrw

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure real(${ck}$) module function stdlib${ii}$_${ci}$la_gbrpvgrw( n, kl, ku, ncols, ab,ldab, afb, ldafb )
           integer(${ik}$), intent(in) :: n, kl, ku, ncols, ldab, ldafb
           complex(${ck}$), intent(in) :: ab(ldab,*), afb(ldafb,*)
     end function stdlib${ii}$_${ci}$la_gbrpvgrw

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, iwork, info &
               )
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: d(*), dl(*), du(*), du2(*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_sgtcon

     pure module subroutine stdlib${ii}$_dgtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, iwork, info &
               )
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: d(*), dl(*), du(*), du2(*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dgtcon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, iwork, info &
               )
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: d(*), dl(*), du(*), du2(*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$gtcon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, info )
               
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: d(*), dl(*), du(*), du2(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_cgtcon

     pure module subroutine stdlib${ii}$_zgtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, info )
               
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: d(*), dl(*), du(*), du2(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zgtcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gtcon( norm, n, dl, d, du, du2, ipiv, anorm, rcond,work, info )
               
           character, intent(in) :: norm
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: d(*), dl(*), du(*), du2(*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$gtcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: d(*), dl(*), du(*)
           real(sp), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_sgttrf

     pure module subroutine stdlib${ii}$_dgttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: d(*), dl(*), du(*)
           real(dp), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_dgttrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: d(*), dl(*), du(*)
           real(${rk}$), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_${ri}$gttrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: d(*), dl(*), du(*)
           complex(sp), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_cgttrf

     pure module subroutine stdlib${ii}$_zgttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: d(*), dl(*), du(*)
           complex(dp), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_zgttrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gttrf( n, dl, d, du, du2, ipiv, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: d(*), dl(*), du(*)
           complex(${ck}$), intent(out) :: du2(*)
     end subroutine stdlib${ii}$_${ci}$gttrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: b(ldb,*)
           real(sp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_sgttrs

     pure module subroutine stdlib${ii}$_dgttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: b(ldb,*)
           real(dp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_dgttrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: b(ldb,*)
           real(${rk}$), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_${ri}$gttrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_cgttrs

     pure module subroutine stdlib${ii}$_zgttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_zgttrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gttrs( trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_${ci}$gttrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: b(ldb,*)
           real(sp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_sgtts2

     pure module subroutine stdlib${ii}$_dgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: b(ldb,*)
           real(dp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_dgtts2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: b(ldb,*)
           real(${rk}$), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_${ri}$gtts2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_cgtts2

     pure module subroutine stdlib${ii}$_zgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_zgtts2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
           integer(${ik}$), intent(in) :: itrans, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(in) :: d(*), dl(*), du(*), du2(*)
     end subroutine stdlib${ii}$_${ci}$gtts2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_sgtrfs

     pure module subroutine stdlib${ii}$_dgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dgtrfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, iwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$gtrfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_cgtrfs

     pure module subroutine stdlib${ii}$_zgtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zgtrfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gtrfs( trans, n, nrhs, dl, d, du, dlf, df, duf, du2,ipiv, b, ldb, x, &
               ldx, ferr, berr, work, rwork,info )
           character, intent(in) :: trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: b(ldb,*), d(*), df(*), dl(*), dlf(*), du(*), du2(*), duf(*)
                     
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$gtrfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_sgesv

     pure module subroutine stdlib${ii}$_dgesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_dgesv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$gesv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_cgesv

     pure module subroutine stdlib${ii}$_zgesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_zgesv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gesv( n, nrhs, a, lda, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$gesv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_sgesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), c(*), r(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_sgesvx

     module subroutine stdlib${ii}$_dgesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), c(*), r(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dgesvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$gesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), c(*), r(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$gesvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cgesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(inout) :: c(*), r(*)
           complex(sp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cgesvx

     module subroutine stdlib${ii}$_zgesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(inout) :: c(*), r(*)
           complex(dp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zgesvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$gesvx( fact, trans, n, nrhs, a, lda, af, ldaf, ipiv,equed, r, c, b, ldb, &
               x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(inout) :: c(*), r(*)
           complex(${ck}$), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$gesvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_sgbsv

     pure module subroutine stdlib${ii}$_dgbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_dgbsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$gbsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_cgbsv

     pure module subroutine stdlib${ii}$_zgbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_zgbsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gbsv( n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$gbsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_sgbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), c(*), r(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_sgbsvx

     module subroutine stdlib${ii}$_dgbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), c(*), r(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dgbsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$gbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), c(*), r(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$gbsvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cgbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(inout) :: c(*), r(*)
           complex(sp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cgbsvx

     module subroutine stdlib${ii}$_zgbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(inout) :: c(*), r(*)
           complex(dp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zgbsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$gbsvx( fact, trans, n, kl, ku, nrhs, ab, ldab, afb,ldafb, ipiv, equed, r, &
               c, b, ldb, x, ldx,rcond, ferr, berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kl, ku, ldab, ldafb, ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(inout) :: c(*), r(*)
           complex(${ck}$), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$gbsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_sgtsv

     pure module subroutine stdlib${ii}$_dgtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_dgtsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_${ri}$gtsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(sp), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_cgtsv

     pure module subroutine stdlib${ii}$_zgtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(dp), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_zgtsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gtsv( n, nrhs, dl, d, du, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(${ck}$), intent(inout) :: b(ldb,*), d(*), dl(*), du(*)
     end subroutine stdlib${ii}$_${ci}$gtsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sgtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(sp), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
     end subroutine stdlib${ii}$_sgtsvx

     pure module subroutine stdlib${ii}$_dgtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(dp), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
     end subroutine stdlib${ii}$_dgtsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$gtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(${rk}$), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
     end subroutine stdlib${ii}$_${ri}$gtsvx

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cgtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           complex(sp), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cgtsvx

     pure module subroutine stdlib${ii}$_zgtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           complex(dp), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zgtsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$gtsvx( fact, trans, n, nrhs, dl, d, du, dlf, df, duf,du2, ipiv, b, &
               ldb, x, ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(in) :: fact, trans
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: b(ldb,*), d(*), dl(*), du(*)
           complex(${ck}$), intent(inout) :: df(*), dlf(*), du2(*), duf(*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$gtsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spocon( uplo, n, a, lda, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           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}$_spocon

     pure module subroutine stdlib${ii}$_dpocon( uplo, n, a, lda, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           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}$_dpocon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pocon( uplo, n, a, lda, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           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}$pocon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpocon( uplo, n, a, lda, anorm, rcond, work, rwork,info )
           character, intent(in) :: uplo
           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}$_cpocon

     pure module subroutine stdlib${ii}$_zpocon( uplo, n, a, lda, anorm, rcond, work, rwork,info )
           character, intent(in) :: uplo
           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}$_zpocon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pocon( uplo, n, a, lda, anorm, rcond, work, rwork,info )
           character, intent(in) :: uplo
           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}$pocon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spotrf( 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}$_spotrf

     pure module subroutine stdlib${ii}$_dpotrf( 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}$_dpotrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$potrf( 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}$potrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpotrf( 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}$_cpotrf

     pure module subroutine stdlib${ii}$_zpotrf( 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}$_zpotrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$potrf( 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}$potrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure recursive module subroutine stdlib${ii}$_spotrf2( 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}$_spotrf2

     pure recursive module subroutine stdlib${ii}$_dpotrf2( 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}$_dpotrf2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure recursive module subroutine stdlib${ii}$_${ri}$potrf2( 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}$potrf2

#:endif
#:endfor

     pure recursive module subroutine stdlib${ii}$_cpotrf2( 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}$_cpotrf2

     pure recursive module subroutine stdlib${ii}$_zpotrf2( 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}$_zpotrf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure recursive module subroutine stdlib${ii}$_${ci}$potrf2( 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}$potrf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spotf2( 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}$_spotf2

     pure module subroutine stdlib${ii}$_dpotf2( 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}$_dpotf2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$potf2( 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}$potf2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpotf2( 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}$_cpotf2

     pure module subroutine stdlib${ii}$_zpotf2( 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}$_zpotf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$potf2( 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}$potf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(sp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_spstrf

     pure module subroutine stdlib${ii}$_dpstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(dp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_dpstrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(${rk}$), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_${ri}$pstrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(sp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_cpstrf

     pure module subroutine stdlib${ii}$_zpstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(dp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_zpstrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pstrf( uplo, n, a, lda, piv, rank, tol, work, info )
           real(${ck}$), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(${ck}$), intent(inout) :: a(lda,*)
           real(${ck}$), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_${ci}$pstrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(sp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_spstf2

     pure module subroutine stdlib${ii}$_dpstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(dp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_dpstf2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(${rk}$), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_${ri}$pstf2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(sp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_cpstf2

     pure module subroutine stdlib${ii}$_zpstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(dp), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_zpstf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pstf2( uplo, n, a, lda, piv, rank, tol, work, info )
           real(${ck}$), intent(in) :: tol
           integer(${ik}$), intent(out) :: info, rank
           integer(${ik}$), intent(in) :: lda, n
           character, intent(in) :: uplo
           complex(${ck}$), intent(inout) :: a(lda,*)
           real(${ck}$), intent(out) :: work(2_${ik}$*n)
           integer(${ik}$), intent(out) :: piv(n)
     end subroutine stdlib${ii}$_${ci}$pstf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spotrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$_spotrs

     pure module subroutine stdlib${ii}$_dpotrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$_dpotrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$potrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$potrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpotrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$_cpotrs

     pure module subroutine stdlib${ii}$_zpotrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$_zpotrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$potrs( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: 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}$potrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spotri( 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}$_spotri

     pure module subroutine stdlib${ii}$_dpotri( 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}$_dpotri

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$potri( 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}$potri

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpotri( 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}$_cpotri

     pure module subroutine stdlib${ii}$_zpotri( 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}$_zpotri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$potri( 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}$potri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sporfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$_sporfs

     pure module subroutine stdlib${ii}$_dporfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$_dporfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$porfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$porfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cporfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$_cporfs

     pure module subroutine stdlib${ii}$_zporfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$_zporfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$porfs( uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x,ldx, ferr, berr, &
               work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           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}$porfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spoequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(in) :: a(lda,*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_spoequ

     pure module subroutine stdlib${ii}$_dpoequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(in) :: a(lda,*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_dpoequ

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$poequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${rk}$), intent(out) :: amax, scond
           real(${rk}$), intent(in) :: a(lda,*)
           real(${rk}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ri}$poequ

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpoequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(out) :: s(*)
           complex(sp), intent(in) :: a(lda,*)
     end subroutine stdlib${ii}$_cpoequ

     pure module subroutine stdlib${ii}$_zpoequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(out) :: s(*)
           complex(dp), intent(in) :: a(lda,*)
     end subroutine stdlib${ii}$_zpoequ

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$poequ( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(out) :: amax, scond
           real(${ck}$), intent(out) :: s(*)
           complex(${ck}$), intent(in) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$poequ

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spoequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(in) :: a(lda,*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_spoequb

     pure module subroutine stdlib${ii}$_dpoequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(in) :: a(lda,*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_dpoequb

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$poequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${rk}$), intent(out) :: amax, scond
           real(${rk}$), intent(in) :: a(lda,*)
           real(${rk}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ri}$poequb

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpoequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           complex(sp), intent(in) :: a(lda,*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_cpoequb

     pure module subroutine stdlib${ii}$_zpoequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           complex(dp), intent(in) :: a(lda,*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_zpoequb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$poequb( n, a, lda, s, scond, amax, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(out) :: amax, scond
           complex(${ck}$), intent(in) :: a(lda,*)
           real(${ck}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ci}$poequb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_claqhe( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(in) :: s(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_claqhe

     pure module subroutine stdlib${ii}$_zlaqhe( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(in) :: s(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zlaqhe

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqhe( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: amax, scond
           real(${ck}$), intent(in) :: s(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$laqhe

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     real(sp) module function stdlib${ii}$_sla_porcond( uplo, n, a, lda, af, ldaf, cmode, c,info, work, iwork )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, ldaf, cmode
           integer(${ik}$), intent(out) :: info
           real(sp), intent(in) :: a(lda,*), af(ldaf,*), c(*)
           real(sp), intent(out) :: work(*)
           integer(${ik}$), intent(out) :: iwork(*)
     end function stdlib${ii}$_sla_porcond

     real(dp) module function stdlib${ii}$_dla_porcond( uplo, n, a, lda, af, ldaf,cmode, c, info, work,iwork )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, ldaf, cmode
           integer(${ik}$), intent(out) :: info
           real(dp), intent(in) :: a(lda,*), af(ldaf,*), c(*)
           real(dp), intent(out) :: work(*)
           integer(${ik}$), intent(out) :: iwork(*)
     end function stdlib${ii}$_dla_porcond

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     real(${rk}$) module function stdlib${ii}$_${ri}$la_porcond( uplo, n, a, lda, af, ldaf,cmode, c, info, work,iwork )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, ldaf, cmode
           integer(${ik}$), intent(out) :: info
           real(${rk}$), intent(in) :: a(lda,*), af(ldaf,*), c(*)
           real(${rk}$), intent(out) :: work(*)
           integer(${ik}$), intent(out) :: iwork(*)
     end function stdlib${ii}$_${ri}$la_porcond

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     real(sp) module function stdlib${ii}$_sla_porpvgrw( uplo, ncols, a, lda, af, ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           real(sp), intent(in) :: a(lda,*), af(ldaf,*)
           real(sp), intent(out) :: work(*)
     end function stdlib${ii}$_sla_porpvgrw

     real(dp) module function stdlib${ii}$_dla_porpvgrw( uplo, ncols, a, lda, af,ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           real(dp), intent(in) :: a(lda,*), af(ldaf,*)
           real(dp), intent(out) :: work(*)
     end function stdlib${ii}$_dla_porpvgrw

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     real(${rk}$) module function stdlib${ii}$_${ri}$la_porpvgrw( uplo, ncols, a, lda, af,ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           real(${rk}$), intent(in) :: a(lda,*), af(ldaf,*)
           real(${rk}$), intent(out) :: work(*)
     end function stdlib${ii}$_${ri}$la_porpvgrw

#:endif
#:endfor

     real(sp) module function stdlib${ii}$_cla_porpvgrw( uplo, ncols, a, lda, af, ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           complex(sp), intent(in) :: a(lda,*), af(ldaf,*)
           real(sp), intent(out) :: work(*)
     end function stdlib${ii}$_cla_porpvgrw

     real(dp) module function stdlib${ii}$_zla_porpvgrw( uplo, ncols, a, lda, af,ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           complex(dp), intent(in) :: a(lda,*), af(ldaf,*)
           real(dp), intent(out) :: work(*)
     end function stdlib${ii}$_zla_porpvgrw

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     real(${ck}$) module function stdlib${ii}$_${ci}$la_porpvgrw( uplo, ncols, a, lda, af,ldaf, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: ncols, lda, ldaf
           complex(${ck}$), intent(in) :: a(lda,*), af(ldaf,*)
           real(${ck}$), intent(out) :: work(*)
     end function stdlib${ii}$_${ci}$la_porpvgrw

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sppcon( uplo, n, ap, anorm, rcond, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: ap(*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_sppcon

     pure module subroutine stdlib${ii}$_dppcon( uplo, n, ap, anorm, rcond, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: ap(*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dppcon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ppcon( uplo, n, ap, anorm, rcond, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(in) :: anorm
           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}$ppcon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cppcon( uplo, n, ap, anorm, rcond, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           real(sp), intent(out) :: rwork(*)
           complex(sp), intent(in) :: ap(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_cppcon

     pure module subroutine stdlib${ii}$_zppcon( uplo, n, ap, anorm, rcond, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           real(dp), intent(out) :: rwork(*)
           complex(dp), intent(in) :: ap(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zppcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ppcon( uplo, n, ap, anorm, rcond, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: anorm
           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}$ppcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_spptrf

     pure module subroutine stdlib${ii}$_dpptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_dpptrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ri}$pptrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_cpptrf

     pure module subroutine stdlib${ii}$_zpptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zpptrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pptrf( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$pptrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$_spptrs

     pure module subroutine stdlib${ii}$_dpptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$_dpptrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$pptrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$_cpptrs

     pure module subroutine stdlib${ii}$_zpptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$_zpptrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pptrs( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: 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}$pptrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_spptri

     pure module subroutine stdlib${ii}$_dpptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_dpptri

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ri}$pptri

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_cpptri

     pure module subroutine stdlib${ii}$_zpptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zpptri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pptri( uplo, n, ap, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$pptri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_spprfs

     pure module subroutine stdlib${ii}$_dpprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dpprfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$pprfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               rwork, info )
           character, intent(in) :: 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) :: afp(*), ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_cpprfs

     pure module subroutine stdlib${ii}$_zpprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               rwork, info )
           character, intent(in) :: 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) :: afp(*), ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zpprfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pprfs( uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr,berr, work, &
               rwork, info )
           character, intent(in) :: 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) :: afp(*), ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$pprfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(in) :: ap(*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_sppequ

     pure module subroutine stdlib${ii}$_dppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(in) :: ap(*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_dppequ

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(out) :: amax, scond
           real(${rk}$), intent(in) :: ap(*)
           real(${rk}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ri}$ppequ

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(out) :: s(*)
           complex(sp), intent(in) :: ap(*)
     end subroutine stdlib${ii}$_cppequ

     pure module subroutine stdlib${ii}$_zppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(out) :: s(*)
           complex(dp), intent(in) :: ap(*)
     end subroutine stdlib${ii}$_zppequ

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ppequ( uplo, n, ap, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(out) :: amax, scond
           real(${ck}$), intent(out) :: s(*)
           complex(${ck}$), intent(in) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$ppequ

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_claqhp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(in) :: s(*)
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_claqhp

     pure module subroutine stdlib${ii}$_zlaqhp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(in) :: s(*)
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zlaqhp

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqhp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: amax, scond
           real(${ck}$), intent(in) :: s(*)
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$laqhp

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           real(sp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_spftrf

     pure module subroutine stdlib${ii}$_dpftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           real(dp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_dpftrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           real(${rk}$), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_${ri}$pftrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           complex(sp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_cpftrf

     pure module subroutine stdlib${ii}$_zpftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           complex(dp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_zpftrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pftrf( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: info
           complex(${ck}$), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_${ci}$pftrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(in) :: a(0_${ik}$:*)
           real(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_spftrs

     pure module subroutine stdlib${ii}$_dpftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(in) :: a(0_${ik}$:*)
           real(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_dpftrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(in) :: a(0_${ik}$:*)
           real(${rk}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$pftrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(sp), intent(in) :: a(0_${ik}$:*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_cpftrs

     pure module subroutine stdlib${ii}$_zpftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(dp), intent(in) :: a(0_${ik}$:*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zpftrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pftrs( transr, uplo, n, nrhs, a, b, ldb, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(${ck}$), intent(in) :: a(0_${ik}$:*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$pftrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_spftri

     pure module subroutine stdlib${ii}$_dpftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_dpftri

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_${ri}$pftri

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(sp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_cpftri

     pure module subroutine stdlib${ii}$_zpftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(dp), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_zpftri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pftri( transr, uplo, n, a, info )
           character, intent(in) :: transr, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           complex(${ck}$), intent(inout) :: a(0_${ik}$:*)
     end subroutine stdlib${ii}$_${ci}$pftri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(in) :: anorm
           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}$_spbcon

     pure module subroutine stdlib${ii}$_dpbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(in) :: anorm
           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}$_dpbcon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${rk}$), intent(in) :: anorm
           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}$pbcon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,rwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(in) :: anorm
           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}$_cpbcon

     pure module subroutine stdlib${ii}$_zpbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,rwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(in) :: anorm
           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}$_zpbcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbcon( uplo, n, kd, ab, ldab, anorm, rcond, work,rwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${ck}$), intent(in) :: anorm
           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}$pbcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_spbtrf

     pure module subroutine stdlib${ii}$_dpbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_dpbtrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${rk}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ri}$pbtrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_cpbtrf

     pure module subroutine stdlib${ii}$_zpbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zpbtrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbtrf( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(${ck}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$pbtrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_spbtf2

     pure module subroutine stdlib${ii}$_dpbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_dpbtf2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${rk}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ri}$pbtf2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_cpbtf2

     pure module subroutine stdlib${ii}$_zpbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zpbtf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbtf2( uplo, n, kd, ab, ldab, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           complex(${ck}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$pbtf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$_spbtrs

     pure module subroutine stdlib${ii}$_dpbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$_dpbtrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$pbtrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$_cpbtrs

     pure module subroutine stdlib${ii}$_zpbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$_zpbtrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbtrs( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: 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}$pbtrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_spbrfs

     pure module subroutine stdlib${ii}$_dpbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dpbrfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$pbrfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_cpbrfs

     pure module subroutine stdlib${ii}$_zpbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zpbrfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbrfs( uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b,ldb, x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$pbrfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(in) :: ab(ldab,*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_spbequ

     pure module subroutine stdlib${ii}$_dpbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(in) :: ab(ldab,*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_dpbequ

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${rk}$), intent(out) :: amax, scond
           real(${rk}$), intent(in) :: ab(ldab,*)
           real(${rk}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ri}$pbequ

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(out) :: amax, scond
           real(sp), intent(out) :: s(*)
           complex(sp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_cpbequ

     pure module subroutine stdlib${ii}$_zpbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(out) :: amax, scond
           real(dp), intent(out) :: s(*)
           complex(dp), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zpbequ

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbequ( uplo, n, kd, ab, ldab, s, scond, amax, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${ck}$), intent(out) :: amax, scond
           real(${ck}$), intent(out) :: s(*)
           complex(${ck}$), intent(in) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$pbequ

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_claqhb( uplo, n, kd, ab, ldab, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(out) :: s(*)
           complex(sp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_claqhb

     pure module subroutine stdlib${ii}$_zlaqhb( uplo, n, kd, ab, ldab, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(out) :: s(*)
           complex(dp), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_zlaqhb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqhb( uplo, n, kd, ab, ldab, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: kd, ldab, n
           real(${ck}$), intent(in) :: amax, scond
           real(${ck}$), intent(out) :: s(*)
           complex(${ck}$), intent(inout) :: ab(ldab,*)
     end subroutine stdlib${ii}$_${ci}$laqhb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sptcon( n, d, e, anorm, rcond, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           real(sp), intent(in) :: d(*), e(*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_sptcon

     pure module subroutine stdlib${ii}$_dptcon( n, d, e, anorm, rcond, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           real(dp), intent(in) :: d(*), e(*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dptcon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ptcon( n, d, e, anorm, rcond, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(in) :: anorm
           real(${rk}$), intent(out) :: rcond
           real(${rk}$), intent(in) :: d(*), e(*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$ptcon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cptcon( n, d, e, anorm, rcond, rwork, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           real(sp), intent(in) :: d(*)
           real(sp), intent(out) :: rwork(*)
           complex(sp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_cptcon

     pure module subroutine stdlib${ii}$_zptcon( n, d, e, anorm, rcond, rwork, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           real(dp), intent(in) :: d(*)
           real(dp), intent(out) :: rwork(*)
           complex(dp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_zptcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ptcon( n, d, e, anorm, rcond, rwork, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           real(${ck}$), intent(in) :: d(*)
           real(${ck}$), intent(out) :: rwork(*)
           complex(${ck}$), intent(in) :: e(*)
     end subroutine stdlib${ii}$_${ci}$ptcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(inout) :: d(*), e(*)
     end subroutine stdlib${ii}$_spttrf

     pure module subroutine stdlib${ii}$_dpttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(inout) :: d(*), e(*)
     end subroutine stdlib${ii}$_dpttrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(inout) :: d(*), e(*)
     end subroutine stdlib${ii}$_${ri}$pttrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(inout) :: d(*)
           complex(sp), intent(inout) :: e(*)
     end subroutine stdlib${ii}$_cpttrf

     pure module subroutine stdlib${ii}$_zpttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(inout) :: d(*)
           complex(dp), intent(inout) :: e(*)
     end subroutine stdlib${ii}$_zpttrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pttrf( n, d, e, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(inout) :: d(*)
           complex(${ck}$), intent(inout) :: e(*)
     end subroutine stdlib${ii}$_${ci}$pttrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spttrs( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: b(ldb,*)
           real(sp), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_spttrs

     pure module subroutine stdlib${ii}$_dpttrs( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: b(ldb,*)
           real(dp), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_dpttrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pttrs( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(inout) :: b(ldb,*)
           real(${rk}$), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_${ri}$pttrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpttrs( uplo, n, nrhs, d, e, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(in) :: d(*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_cpttrs

     pure module subroutine stdlib${ii}$_zpttrs( uplo, n, nrhs, d, e, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(in) :: d(*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_zpttrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pttrs( uplo, n, nrhs, d, e, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${ck}$), intent(in) :: d(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(in) :: e(*)
     end subroutine stdlib${ii}$_${ci}$pttrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sptts2( n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: b(ldb,*)
           real(sp), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_sptts2

     pure module subroutine stdlib${ii}$_dptts2( n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: b(ldb,*)
           real(dp), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_dptts2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ptts2( n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(inout) :: b(ldb,*)
           real(${rk}$), intent(in) :: d(*), e(*)
     end subroutine stdlib${ii}$_${ri}$ptts2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cptts2( iuplo, n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: iuplo, ldb, n, nrhs
           real(sp), intent(in) :: d(*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_cptts2

     pure module subroutine stdlib${ii}$_zptts2( iuplo, n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: iuplo, ldb, n, nrhs
           real(dp), intent(in) :: d(*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(in) :: e(*)
     end subroutine stdlib${ii}$_zptts2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ptts2( iuplo, n, nrhs, d, e, b, ldb )
           integer(${ik}$), intent(in) :: iuplo, ldb, n, nrhs
           real(${ck}$), intent(in) :: d(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(in) :: e(*)
     end subroutine stdlib${ii}$_${ci}$ptts2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sptrfs( n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr,berr, work, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(in) :: b(ldb,*), d(*), df(*), e(*), ef(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_sptrfs

     pure module subroutine stdlib${ii}$_dptrfs( n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr,berr, work, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(in) :: b(ldb,*), d(*), df(*), e(*), ef(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dptrfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ptrfs( n, nrhs, d, e, df, ef, b, ldb, x, ldx, ferr,berr, work, info )
               
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${rk}$), intent(in) :: b(ldb,*), d(*), df(*), e(*), ef(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$ptrfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cptrfs( uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx,ferr, berr, work, &
               rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(in) :: d(*), df(*)
           complex(sp), intent(in) :: b(ldb,*), e(*), ef(*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_cptrfs

     pure module subroutine stdlib${ii}$_zptrfs( uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx,ferr, berr, work, &
               rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(in) :: d(*), df(*)
           complex(dp), intent(in) :: b(ldb,*), e(*), ef(*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zptrfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ptrfs( uplo, n, nrhs, d, e, df, ef, b, ldb, x, ldx,ferr, berr, work, &
               rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(in) :: d(*), df(*)
           complex(${ck}$), intent(in) :: b(ldb,*), e(*), ef(*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$ptrfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slaqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(inout) :: ap(*)
           real(sp), intent(in) :: s(*)
     end subroutine stdlib${ii}$_slaqsp

     pure module subroutine stdlib${ii}$_dlaqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(inout) :: ap(*)
           real(dp), intent(in) :: s(*)
     end subroutine stdlib${ii}$_dlaqsp

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$laqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(${rk}$), intent(in) :: amax, scond
           real(${rk}$), intent(inout) :: ap(*)
           real(${rk}$), intent(in) :: s(*)
     end subroutine stdlib${ii}$_${ri}$laqsp

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_claqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(in) :: s(*)
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_claqsp

     pure module subroutine stdlib${ii}$_zlaqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(in) :: s(*)
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zlaqsp

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqsp( uplo, n, ap, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: amax, scond
           real(${ck}$), intent(in) :: s(*)
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$laqsp

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssycon( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssycon

     pure module subroutine stdlib${ii}$_dsycon( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsycon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sycon( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sycon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csycon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csycon

     pure module subroutine stdlib${ii}$_zsycon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsycon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sycon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sycon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytrf

     pure module subroutine stdlib${ii}$_dsytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytrf

     pure module subroutine stdlib${ii}$_zsytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_slasyf

     pure module subroutine stdlib${ii}$_dlasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_dlasyf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$lasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ri}$lasyf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_clasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_clasyf

     pure module subroutine stdlib${ii}$_zlasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_zlasyf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lasyf( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ci}$lasyf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_ssytf2

     pure module subroutine stdlib${ii}$_dsytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_dsytf2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ri}$sytf2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_csytf2

     pure module subroutine stdlib${ii}$_zsytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zsytf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$sytf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_ssytrs

     pure module subroutine stdlib${ii}$_dsytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_dsytrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$sytrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_csytrs

     pure module subroutine stdlib${ii}$_zsytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_zsytrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$sytrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytri

     pure module subroutine stdlib${ii}$_dsytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytri

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytri

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytri

     pure module subroutine stdlib${ii}$_zsytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           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}$_ssyrfs

     pure module subroutine stdlib${ii}$_dsyrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           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}$_dsyrfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: uplo
           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}$syrfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$_csyrfs

     pure module subroutine stdlib${ii}$_zsyrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$_zsyrfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syrfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$syrfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           real(sp), intent(in) :: a(lda,*)
           real(sp), intent(out) :: s(*), work(*)
     end subroutine stdlib${ii}$_ssyequb

     pure module subroutine stdlib${ii}$_dsyequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           real(dp), intent(in) :: a(lda,*)
           real(dp), intent(out) :: s(*), work(*)
     end subroutine stdlib${ii}$_dsyequb

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${rk}$), intent(out) :: amax, scond
           character, intent(in) :: uplo
           real(${rk}$), intent(in) :: a(lda,*)
           real(${rk}$), intent(out) :: s(*), work(*)
     end subroutine stdlib${ii}$_${ri}$syequb

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_csyequb

     pure module subroutine stdlib${ii}$_zsyequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_zsyequb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
           real(${ck}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ci}$syequb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_ssyconv

     pure module subroutine stdlib${ii}$_dsyconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_dsyconv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: e(*)
     end subroutine stdlib${ii}$_${ri}$syconv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_csyconv

     pure module subroutine stdlib${ii}$_zsyconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_zsyconv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syconv( uplo, way, n, a, lda, ipiv, e, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*)
     end subroutine stdlib${ii}$_${ci}$syconv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytrs2

     pure module subroutine stdlib${ii}$_dsytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytrs2

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytrs2

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytrs2

     pure module subroutine stdlib${ii}$_zsytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytrs2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytrs2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(in) :: a(lda,*), e(*)
           real(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_ssytrs_3

     pure module subroutine stdlib${ii}$_dsytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(in) :: a(lda,*), e(*)
           real(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_dsytrs_3

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(in) :: a(lda,*), e(*)
           real(${rk}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$sytrs_3

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*), e(*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_csytrs_3

     pure module subroutine stdlib${ii}$_zsytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*), e(*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zsytrs_3

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*), e(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$sytrs_3

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           real(sp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_ssyswapr

     pure module subroutine stdlib${ii}$_dsyswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           real(dp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_dsyswapr

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           real(${rk}$), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_${ri}$syswapr

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(sp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_csyswapr

     pure module subroutine stdlib${ii}$_zsyswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(dp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_zsyswapr

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(${ck}$), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_${ci}$syswapr

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     real(sp) module function stdlib${ii}$_cla_herpvgrw( uplo, n, info, a, lda, af, ldaf, ipiv,work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, info, lda, ldaf
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*), af(ldaf,*)
           real(sp), intent(out) :: work(*)
     end function stdlib${ii}$_cla_herpvgrw

     real(dp) module function stdlib${ii}$_zla_herpvgrw( uplo, n, info, a, lda, af,ldaf, ipiv, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, info, lda, ldaf
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*), af(ldaf,*)
           real(dp), intent(out) :: work(*)
     end function stdlib${ii}$_zla_herpvgrw

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     real(${ck}$) module function stdlib${ii}$_${ci}$la_herpvgrw( uplo, n, info, a, lda, af,ldaf, ipiv, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, info, lda, ldaf
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*), af(ldaf,*)
           real(${ck}$), intent(out) :: work(*)
     end function stdlib${ii}$_${ci}$la_herpvgrw

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sspcon( uplo, n, ap, ipiv, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: ap(*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_sspcon

     pure module subroutine stdlib${ii}$_dspcon( uplo, n, ap, ipiv, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: ap(*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dspcon

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$spcon( uplo, n, ap, ipiv, anorm, rcond, work, iwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: 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) :: ap(*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$spcon

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cspcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: ap(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_cspcon

     pure module subroutine stdlib${ii}$_zspcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: ap(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zspcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$spcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: ap(*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$spcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_ssptrf

     pure module subroutine stdlib${ii}$_dsptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_dsptrf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ri}$sptrf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_csptrf

     pure module subroutine stdlib${ii}$_zsptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zsptrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$sptrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(in) :: ap(*)
           real(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_ssptrs

     pure module subroutine stdlib${ii}$_dsptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(in) :: ap(*)
           real(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_dsptrs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(in) :: ap(*)
           real(${rk}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$sptrs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: ap(*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_csptrs

     pure module subroutine stdlib${ii}$_zsptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: ap(*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zsptrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: ap(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$sptrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: ap(*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssptri

     pure module subroutine stdlib${ii}$_dsptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: ap(*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsptri

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: ap(*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sptri

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csptri

     pure module subroutine stdlib${ii}$_zsptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsptri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sptri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*)
           real(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_ssprfs

     pure module subroutine stdlib${ii}$_dsprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*)
           real(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_dsprfs

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                iwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: afp(*), ap(*), b(ldb,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*)
           real(${rk}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$sprfs

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_csprfs

     pure module subroutine stdlib${ii}$_zsprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zsprfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$sprfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssycon_rook

     pure module subroutine stdlib${ii}$_dsycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsycon_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,iwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, 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) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sycon_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csycon_rook

     pure module subroutine stdlib${ii}$_zsycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsycon_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sycon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sycon_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytrf_rook

     pure module subroutine stdlib${ii}$_dsytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytrf_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytrf_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytrf_rook

     pure module subroutine stdlib${ii}$_zsytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytrf_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytrf_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_slasyf_rook

     pure module subroutine stdlib${ii}$_dlasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_dlasyf_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$lasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ri}$lasyf_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_clasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_clasyf_rook

     pure module subroutine stdlib${ii}$_zlasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_zlasyf_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lasyf_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ci}$lasyf_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_ssytf2_rook

     pure module subroutine stdlib${ii}$_dsytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_dsytf2_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ri}$sytf2_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_csytf2_rook

     pure module subroutine stdlib${ii}$_zsytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zsytf2_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$sytf2_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_ssytrs_rook

     pure module subroutine stdlib${ii}$_dsytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_dsytrs_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$sytrs_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_csytrs_rook

     pure module subroutine stdlib${ii}$_zsytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_zsytrs_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$sytrs_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytri_rook

     pure module subroutine stdlib${ii}$_dsytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytri_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytri_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytri_rook

     pure module subroutine stdlib${ii}$_zsytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytri_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytri_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_ssytrf_rk

     pure module subroutine stdlib${ii}$_dsytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_dsytrf_rk

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ri}$sytrf_rk

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_csytrf_rk

     pure module subroutine stdlib${ii}$_zsytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_zsytrf_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ci}$sytrf_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_slasyf_rk

     pure module subroutine stdlib${ii}$_dlasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_dlasyf_rk

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$lasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_${ri}$lasyf_rk

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_clasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_clasyf_rk

     pure module subroutine stdlib${ii}$_zlasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_zlasyf_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lasyf_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*), w(ldw,*)
     end subroutine stdlib${ii}$_${ci}$lasyf_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_ssytf2_rk

     pure module subroutine stdlib${ii}$_dsytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_dsytf2_rk

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: e(*)
     end subroutine stdlib${ii}$_${ri}$sytf2_rk

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_csytf2_rk

     pure module subroutine stdlib${ii}$_zsytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_zsytf2_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*)
     end subroutine stdlib${ii}$_${ci}$sytf2_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_ssyconvf

     pure module subroutine stdlib${ii}$_dsyconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_dsyconvf

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_${ri}$syconvf

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_csyconvf

     pure module subroutine stdlib${ii}$_zsyconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_zsyconvf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syconvf( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(inout) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_${ci}$syconvf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssyconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_ssyconvf_rook

     pure module subroutine stdlib${ii}$_dsyconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_dsyconvf_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$syconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_${ri}$syconvf_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csyconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_csyconvf_rook

     pure module subroutine stdlib${ii}$_zsyconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_zsyconvf_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$syconvf_rook( uplo, way, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo, way
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), e(*)
     end subroutine stdlib${ii}$_${ci}$syconvf_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytrf_aa

     pure module subroutine stdlib${ii}$_dsytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytrf_aa

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytrf_aa

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytrf_aa

     pure module subroutine stdlib${ii}$_zsytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytrf_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytrf_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), h(ldh,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_slasyf_aa

     pure module subroutine stdlib${ii}$_dlasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), h(ldh,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dlasyf_aa

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$lasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), h(ldh,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$lasyf_aa

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_clasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), h(ldh,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_clasyf_aa

     pure module subroutine stdlib${ii}$_zlasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), h(ldh,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zlasyf_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lasyf_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), h(ldh,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$lasyf_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(in) :: a(lda,*)
           real(sp), intent(inout) :: b(ldb,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssytrs_aa

     pure module subroutine stdlib${ii}$_dsytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(in) :: a(lda,*)
           real(dp), intent(inout) :: b(ldb,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsytrs_aa

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${rk}$), intent(in) :: a(lda,*)
           real(${rk}$), intent(inout) :: b(ldb,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sytrs_aa

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csytrs_aa

     pure module subroutine stdlib${ii}$_zsytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsytrs_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sytrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sytrs_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_checon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_checon

     pure module subroutine stdlib${ii}$_zhecon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhecon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hecon( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hecon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetrf

     pure module subroutine stdlib${ii}$_zhetrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrf( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_clahef( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_clahef

     pure module subroutine stdlib${ii}$_zlahef( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_zlahef

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lahef( uplo, n, nb, kb, a, lda, ipiv, w, ldw, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ci}$lahef

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_chetf2

     pure module subroutine stdlib${ii}$_zhetf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zhetf2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetf2( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$hetf2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_chetrs

     pure module subroutine stdlib${ii}$_zhetrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$_zhetrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrs( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           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}$hetrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetri

     pure module subroutine stdlib${ii}$_zhetri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetri( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_cherfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$_cherfs

     pure module subroutine stdlib${ii}$_zherfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$_zherfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$herfs( uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb,x, ldx, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: uplo
           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}$herfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_cheequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
           real(sp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_cheequb

     pure module subroutine stdlib${ii}$_zheequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
           real(dp), intent(out) :: s(*)
     end subroutine stdlib${ii}$_zheequb

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$heequb( uplo, n, a, lda, s, scond, amax, work, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(out) :: amax, scond
           character, intent(in) :: uplo
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
           real(${ck}$), intent(out) :: s(*)
     end subroutine stdlib${ii}$_${ci}$heequb

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetrs2

     pure module subroutine stdlib${ii}$_zhetrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetrs2

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrs2( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetrs2

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*), e(*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_chetrs_3

     pure module subroutine stdlib${ii}$_zhetrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*), e(*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zhetrs_3

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrs_3( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*), e(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$hetrs_3

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_cheswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(sp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_cheswapr

     pure module subroutine stdlib${ii}$_zheswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(dp), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_zheswapr

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$heswapr( uplo, n, a, lda, i1, i2)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: i1, i2, lda, n
           complex(${ck}$), intent(inout) :: a(lda,n)
     end subroutine stdlib${ii}$_${ci}$heswapr

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chpcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: ap(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chpcon

     pure module subroutine stdlib${ii}$_zhpcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: ap(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhpcon

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hpcon( uplo, n, ap, ipiv, anorm, rcond, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: ap(*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hpcon

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_chptrf

     pure module subroutine stdlib${ii}$_zhptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_zhptrf

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hptrf( uplo, n, ap, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*)
     end subroutine stdlib${ii}$_${ci}$hptrf

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: ap(*)
           complex(sp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_chptrs

     pure module subroutine stdlib${ii}$_zhptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: ap(*)
           complex(dp), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_zhptrs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hptrs( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: ap(*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$hptrs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chptri

     pure module subroutine stdlib${ii}$_zhptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhptri

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hptri( uplo, n, ap, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hptri

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
           complex(sp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_chprfs

     pure module subroutine stdlib${ii}$_zhprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
           complex(dp), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_zhprfs

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hprfs( uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx,ferr, berr, work,&
                rwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           integer(${ik}$), intent(in) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: afp(*), ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
           complex(${ck}$), intent(inout) :: x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$hprfs

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_checon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: anorm
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_checon_rook

     pure module subroutine stdlib${ii}$_zhecon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: anorm
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhecon_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hecon_rook( uplo, n, a, lda, ipiv, anorm, rcond, work,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: anorm
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hecon_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetrf_rook

     pure module subroutine stdlib${ii}$_zhetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetrf_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetrf_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_clahef_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_clahef_rook

     pure module subroutine stdlib${ii}$_zlahef_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_zlahef_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lahef_rook( uplo, n, nb, kb, a, lda, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: w(ldw,*)
     end subroutine stdlib${ii}$_${ci}$lahef_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_chetf2_rook

     pure module subroutine stdlib${ii}$_zhetf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zhetf2_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetf2_rook( uplo, n, a, lda, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$hetf2_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_chetrs_rook

     pure module subroutine stdlib${ii}$_zhetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$_zhetrs_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb,info )
           character, intent(in) :: uplo
           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}$hetrs_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetri_rook

     pure module subroutine stdlib${ii}$_zhetri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetri_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetri_rook( uplo, n, a, lda, ipiv, work, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetri_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_chetrf_rk

     pure module subroutine stdlib${ii}$_zhetrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_zhetrf_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrf_rk( uplo, n, a, lda, e, ipiv, work, lwork,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, lwork, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ci}$hetrf_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_clahef_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: w(ldw,*), e(*)
     end subroutine stdlib${ii}$_clahef_rk

     pure module subroutine stdlib${ii}$_zlahef_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: w(ldw,*), e(*)
     end subroutine stdlib${ii}$_zlahef_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lahef_rk( uplo, n, nb, kb, a, lda, e, ipiv, w, ldw,info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info, kb
           integer(${ik}$), intent(in) :: lda, ldw, n, nb
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: w(ldw,*), e(*)
     end subroutine stdlib${ii}$_${ci}$lahef_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_chetf2_rk

     pure module subroutine stdlib${ii}$_zhetf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: e(*)
     end subroutine stdlib${ii}$_zhetf2_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetf2_rk( uplo, n, a, lda, e, ipiv, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, n
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: e(*)
     end subroutine stdlib${ii}$_${ci}$hetf2_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetrf_aa

     pure module subroutine stdlib${ii}$_zhetrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetrf_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrf_aa( uplo, n, a, lda, ipiv, work, lwork, info)
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, lda, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetrf_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_clahef_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), h(ldh,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_clahef_aa

     pure module subroutine stdlib${ii}$_zlahef_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), h(ldh,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zlahef_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$lahef_aa( uplo, j1, m, nb, a, lda, ipiv,h, ldh, work )
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: m, nb, j1, lda, ldh
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), h(ldh,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$lahef_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chetrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(sp), intent(in) :: a(lda,*)
           complex(sp), intent(inout) :: b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chetrs_aa

     pure module subroutine stdlib${ii}$_zhetrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(dp), intent(in) :: a(lda,*)
           complex(dp), intent(inout) :: b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhetrs_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hetrs_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: n, nrhs, lda, ldb, lwork
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ipiv(*)
           complex(${ck}$), intent(in) :: a(lda,*)
           complex(${ck}$), intent(inout) :: b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hetrs_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_slaqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(inout) :: a(lda,*)
           real(sp), intent(in) :: s(*)
     end subroutine stdlib${ii}$_slaqsy

     pure module subroutine stdlib${ii}$_dlaqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(inout) :: a(lda,*)
           real(dp), intent(in) :: s(*)
     end subroutine stdlib${ii}$_dlaqsy

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$laqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(${rk}$), intent(in) :: amax, scond
           real(${rk}$), intent(inout) :: a(lda,*)
           real(${rk}$), intent(in) :: s(*)
     end subroutine stdlib${ii}$_${ri}$laqsy

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_claqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(sp), intent(in) :: amax, scond
           real(sp), intent(in) :: s(*)
           complex(sp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_claqsy

     pure module subroutine stdlib${ii}$_zlaqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(dp), intent(in) :: amax, scond
           real(dp), intent(in) :: s(*)
           complex(dp), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_zlaqsy

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$laqsy( uplo, n, a, lda, s, scond, amax, equed )
           character, intent(out) :: equed
           character, intent(in) :: uplo
           integer(${ik}$), intent(in) :: lda, n
           real(${ck}$), intent(in) :: amax, scond
           real(${ck}$), intent(in) :: s(*)
           complex(${ck}$), intent(inout) :: a(lda,*)
     end subroutine stdlib${ii}$_${ci}$laqsy

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sposv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_sposv

     pure module subroutine stdlib${ii}$_dposv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_dposv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$posv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$posv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cposv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_cposv

     pure module subroutine stdlib${ii}$_zposv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_zposv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$posv( uplo, n, nrhs, a, lda, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, n, nrhs
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$posv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_sposvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), s(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_sposvx

     module subroutine stdlib${ii}$_dposvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), s(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dposvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$posvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*), s(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$posvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cposvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(inout) :: s(*)
           complex(sp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cposvx

     module subroutine stdlib${ii}$_zposvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(inout) :: s(*)
           complex(dp), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zposvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$posvx( fact, uplo, n, nrhs, a, lda, af, ldaf, equed,s, b, ldb, x, ldx, &
               rcond, ferr, berr, work,rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(inout) :: s(*)
           complex(${ck}$), intent(inout) :: a(lda,*), af(ldaf,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$posvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_sppsv

     pure module subroutine stdlib${ii}$_dppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_dppsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$ppsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(sp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_cppsv

     pure module subroutine stdlib${ii}$_zppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(dp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_zppsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ppsv( uplo, n, nrhs, ap, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           complex(${ck}$), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$ppsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_sppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: afp(*), ap(*), b(ldb,*), s(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_sppsvx

     module subroutine stdlib${ii}$_dppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: afp(*), ap(*), b(ldb,*), s(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dppsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$ppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: afp(*), ap(*), b(ldb,*), s(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$ppsvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(inout) :: s(*)
           complex(sp), intent(inout) :: afp(*), ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cppsvx

     module subroutine stdlib${ii}$_zppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(inout) :: s(*)
           complex(dp), intent(inout) :: afp(*), ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zppsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$ppsvx( fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb,x, ldx, rcond, ferr,&
                berr, work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(inout) :: s(*)
           complex(${ck}$), intent(inout) :: afp(*), ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$ppsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_spbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           real(sp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_spbsv

     pure module subroutine stdlib${ii}$_dpbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           real(dp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_dpbsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$pbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           real(${rk}$), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$pbsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cpbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           complex(sp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_cpbsv

     pure module subroutine stdlib${ii}$_zpbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           complex(dp), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_zpbsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$pbsv( uplo, n, kd, nrhs, ab, ldab, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldb, n, nrhs
           complex(${ck}$), intent(inout) :: ab(ldab,*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$pbsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_spbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), s(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_spbsvx

     module subroutine stdlib${ii}$_dpbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), s(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dpbsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$pbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, iwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*), s(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$pbsvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cpbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(inout) :: s(*)
           complex(sp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cpbsvx

     module subroutine stdlib${ii}$_zpbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(inout) :: s(*)
           complex(dp), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zpbsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$pbsvx( fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb,equed, s, b, ldb, x, &
               ldx, rcond, ferr, berr,work, rwork, info )
           character, intent(inout) :: equed
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: kd, ldab, ldafb, ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(inout) :: s(*)
           complex(${ck}$), intent(inout) :: ab(ldab,*), afb(ldafb,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$pbsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: b(ldb,*), d(*), e(*)
     end subroutine stdlib${ii}$_sptsv

     pure module subroutine stdlib${ii}$_dptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: b(ldb,*), d(*), e(*)
     end subroutine stdlib${ii}$_dptsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${rk}$), intent(inout) :: b(ldb,*), d(*), e(*)
     end subroutine stdlib${ii}$_${ri}$ptsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(sp), intent(inout) :: d(*)
           complex(sp), intent(inout) :: b(ldb,*), e(*)
     end subroutine stdlib${ii}$_cptsv

     pure module subroutine stdlib${ii}$_zptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(dp), intent(inout) :: d(*)
           complex(dp), intent(inout) :: b(ldb,*), e(*)
     end subroutine stdlib${ii}$_zptsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ptsv( n, nrhs, d, e, b, ldb, info )
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           real(${ck}$), intent(inout) :: d(*)
           complex(${ck}$), intent(inout) :: b(ldb,*), e(*)
     end subroutine stdlib${ii}$_${ci}$ptsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           real(sp), intent(in) :: b(ldb,*), d(*), e(*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(sp), intent(inout) :: df(*), ef(*)
     end subroutine stdlib${ii}$_sptsvx

     pure module subroutine stdlib${ii}$_dptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           real(dp), intent(in) :: b(ldb,*), d(*), e(*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(dp), intent(inout) :: df(*), ef(*)
     end subroutine stdlib${ii}$_dptsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$ptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           real(${rk}$), intent(in) :: b(ldb,*), d(*), e(*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
           real(${rk}$), intent(inout) :: df(*), ef(*)
     end subroutine stdlib${ii}$_${ri}$ptsvx

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, rwork, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(sp), intent(in) :: d(*)
           real(sp), intent(inout) :: df(*)
           complex(sp), intent(in) :: b(ldb,*), e(*)
           complex(sp), intent(inout) :: ef(*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cptsvx

     pure module subroutine stdlib${ii}$_zptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, rwork, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           real(dp), intent(in) :: d(*)
           real(dp), intent(inout) :: df(*)
           complex(dp), intent(in) :: b(ldb,*), e(*)
           complex(dp), intent(inout) :: ef(*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zptsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$ptsvx( fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx,rcond, ferr, berr,&
                work, rwork, info )
           character, intent(in) :: fact
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           real(${ck}$), intent(in) :: d(*)
           real(${ck}$), intent(inout) :: df(*)
           complex(${ck}$), intent(in) :: b(ldb,*), e(*)
           complex(${ck}$), intent(inout) :: ef(*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$ptsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssysv

     pure module subroutine stdlib${ii}$_dsysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsysv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sysv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csysv

     pure module subroutine stdlib${ii}$_zsysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsysv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sysv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sysv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_ssysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(in) :: a(lda,*), b(ldb,*)
           real(sp), intent(inout) :: af(ldaf,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_ssysvx

     module subroutine stdlib${ii}$_dsysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(in) :: a(lda,*), b(ldb,*)
           real(dp), intent(inout) :: af(ldaf,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dsysvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$sysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(in) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(inout) :: af(ldaf,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$sysvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_csysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: a(lda,*), b(ldb,*)
           complex(sp), intent(inout) :: af(ldaf,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_csysvx

     module subroutine stdlib${ii}$_zsysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: a(lda,*), b(ldb,*)
           complex(dp), intent(inout) :: af(ldaf,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zsysvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$sysvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(inout) :: af(ldaf,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$sysvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
           real(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_ssysv_rk

     pure module subroutine stdlib${ii}$_dsysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
           real(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_dsysv_rk

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb,work, lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ri}$sysv_rk

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_csysv_rk

     pure module subroutine stdlib${ii}$_zsysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_zsysv_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sysv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ci}$sysv_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssysv_rook

     pure module subroutine stdlib${ii}$_dsysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsysv_rook

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sysv_rook

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csysv_rook

     pure module subroutine stdlib${ii}$_zsysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsysv_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sysv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sysv_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chesv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chesv

     pure module subroutine stdlib${ii}$_zhesv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhesv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hesv( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hesv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_chesvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(in) :: a(lda,*), b(ldb,*)
           complex(sp), intent(inout) :: af(ldaf,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_chesvx

     module subroutine stdlib${ii}$_zhesvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(in) :: a(lda,*), b(ldb,*)
           complex(dp), intent(inout) :: af(ldaf,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zhesvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$hesvx( fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b,ldb, x, ldx, rcond, &
               ferr, berr, work, lwork,rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldaf, ldb, ldx, lwork, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(in) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(inout) :: af(ldaf,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$hesvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chesv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_chesv_rk

     pure module subroutine stdlib${ii}$_zhesv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_zhesv_rk

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hesv_rk( uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: e(*), work(*)
     end subroutine stdlib${ii}$_${ci}$hesv_rk

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chesv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chesv_rook

     pure module subroutine stdlib${ii}$_zhesv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhesv_rook

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hesv_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hesv_rook

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_sspsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_sspsv

     pure module subroutine stdlib${ii}$_dspsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_dspsv

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$spsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_${ri}$spsv

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_cspsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_cspsv

     pure module subroutine stdlib${ii}$_zspsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_zspsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$spsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$spsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_sspsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(sp), intent(inout) :: afp(*)
           real(sp), intent(in) :: ap(*), b(ldb,*)
           real(sp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_sspsvx

     module subroutine stdlib${ii}$_dspsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(dp), intent(inout) :: afp(*)
           real(dp), intent(in) :: ap(*), b(ldb,*)
           real(dp), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_dspsvx

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     module subroutine stdlib${ii}$_${ri}$spsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, iwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${rk}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           integer(${ik}$), intent(out) :: iwork(*)
           real(${rk}$), intent(inout) :: afp(*)
           real(${rk}$), intent(in) :: ap(*), b(ldb,*)
           real(${rk}$), intent(out) :: berr(*), ferr(*), work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ri}$spsvx

#:endif
#:endfor

     module subroutine stdlib${ii}$_cspsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(inout) :: afp(*)
           complex(sp), intent(in) :: ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_cspsvx

     module subroutine stdlib${ii}$_zspsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(inout) :: afp(*)
           complex(dp), intent(in) :: ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zspsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$spsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(inout) :: afp(*)
           complex(${ck}$), intent(in) :: ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$spsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chpsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_chpsv

     pure module subroutine stdlib${ii}$_zhpsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_zhpsv

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hpsv( uplo, n, nrhs, ap, ipiv, b, ldb, info )
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: ap(*), b(ldb,*)
     end subroutine stdlib${ii}$_${ci}$hpsv

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     module subroutine stdlib${ii}$_chpsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(sp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(sp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(sp), intent(inout) :: afp(*)
           complex(sp), intent(in) :: ap(*), b(ldb,*)
           complex(sp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_chpsvx

     module subroutine stdlib${ii}$_zhpsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(dp), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(dp), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(dp), intent(inout) :: afp(*)
           complex(dp), intent(in) :: ap(*), b(ldb,*)
           complex(dp), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_zhpsvx

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     module subroutine stdlib${ii}$_${ci}$hpsvx( fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x,ldx, rcond, ferr, &
               berr, work, rwork, info )
           character, intent(in) :: fact, uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: ldb, ldx, n, nrhs
           real(${ck}$), intent(out) :: rcond
           integer(${ik}$), intent(inout) :: ipiv(*)
           real(${ck}$), intent(out) :: berr(*), ferr(*), rwork(*)
           complex(${ck}$), intent(inout) :: afp(*)
           complex(${ck}$), intent(in) :: ap(*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*), x(ldx,*)
     end subroutine stdlib${ii}$_${ci}$hpsvx

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_ssysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(sp), intent(inout) :: a(lda,*), b(ldb,*)
           real(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_ssysv_aa

     pure module subroutine stdlib${ii}$_dsysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(dp), intent(inout) :: a(lda,*), b(ldb,*)
           real(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_dsysv_aa

#:for rk,rt,ri in REAL_KINDS_TYPES
#:if not rk in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ri}$sysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           real(${rk}$), intent(inout) :: a(lda,*), b(ldb,*)
           real(${rk}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ri}$sysv_aa

#:endif
#:endfor

     pure module subroutine stdlib${ii}$_csysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_csysv_aa

     pure module subroutine stdlib${ii}$_zsysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zsysv_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$sysv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$sysv_aa

#:endif
#:endfor

#:endfor
end interface 


interface 
#:for ik,it,ii in LINALG_INT_KINDS_TYPES
     pure module subroutine stdlib${ii}$_chesv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(sp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(sp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_chesv_aa

     pure module subroutine stdlib${ii}$_zhesv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(dp), intent(inout) :: a(lda,*), b(ldb,*)
           complex(dp), intent(out) :: work(*)
     end subroutine stdlib${ii}$_zhesv_aa

#:for ck,ct,ci in CMPLX_KINDS_TYPES
#:if not ck in ["sp","dp"]
     pure module subroutine stdlib${ii}$_${ci}$hesv_aa( uplo, n, nrhs, a, lda, ipiv, b, ldb, work,lwork, info )
               
           character, intent(in) :: uplo
           integer(${ik}$), intent(out) :: info
           integer(${ik}$), intent(in) :: lda, ldb, lwork, n, nrhs
           integer(${ik}$), intent(out) :: ipiv(*)
           complex(${ck}$), intent(inout) :: a(lda,*), b(ldb,*)
           complex(${ck}$), intent(out) :: work(*)
     end subroutine stdlib${ii}$_${ci}$hesv_aa

#:endif
#:endfor

#:endfor
end interface 

end module stdlib_lapack_solve