gsvj1 Interface

public interface gsvj1

GSVJ1 is called from CGESVJ as a pre-processor and that is its main purpose. It applies Jacobi rotations in the same way as CGESVJ does, but it targets only particular pivots and it does not check convergence (stopping criterion). Few tuning parameters (marked by [TP]) are available for the implementer. Further Details ~~~~~~~~~~~~~~~ GSVJ1 applies few sweeps of Jacobi rotations in the column space of the input M-by-N matrix A. The pivot pairs are taken from the (1,2) off-diagonal block in the corresponding N-by-N Gram matrix A^T * A. The block-entries (tiles) of the (1,2) off-diagonal block are marked by the [x]'s in the following scheme: | * * * [x] [x] [x]| | * * * [x] [x] [x]| Row-cycling in the nblr-by-nblc [x] blocks. | * * * [x] [x] [x]| Row-cyclic pivoting inside each [x] block. |[x] [x] [x] * * * | |[x] [x] [x] * * * | |[x] [x] [x] * * * | In terms of the columns of A, the first N1 columns are rotated 'against' the remaining N-N1 columns, trying to increase the angle between the corresponding subspaces. The off-diagonal block is N1-by(N-N1) and it is tiled using quadratic tiles of side KBL. Here, KBL is a tuning parameter. The number of sweeps is given in NSWEEP and the orthogonality threshold is given in TOL.


Subroutines

public pure subroutine cgsvj1(jobv, m, n, n1, a, lda, d, sva, mv, v, ldv, eps, sfmin, tol, nsweep, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobv
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: n1
complex(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=sp), intent(inout) :: d(n)
real(kind=sp), intent(inout) :: sva(n)
integer(kind=ilp), intent(in) :: mv
complex(kind=sp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=sp), intent(in) :: eps
real(kind=sp), intent(in) :: sfmin
real(kind=sp), intent(in) :: tol
integer(kind=ilp), intent(in) :: nsweep
complex(kind=sp), intent(out) :: work(lwork)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

public pure subroutine dgsvj1(jobv, m, n, n1, a, lda, d, sva, mv, v, ldv, eps, sfmin, tol, nsweep, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobv
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: n1
real(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=dp), intent(inout) :: d(n)
real(kind=dp), intent(inout) :: sva(n)
integer(kind=ilp), intent(in) :: mv
real(kind=dp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=dp), intent(in) :: eps
real(kind=dp), intent(in) :: sfmin
real(kind=dp), intent(in) :: tol
integer(kind=ilp), intent(in) :: nsweep
real(kind=dp), intent(out) :: work(lwork)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

public pure subroutine sgsvj1(jobv, m, n, n1, a, lda, d, sva, mv, v, ldv, eps, sfmin, tol, nsweep, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobv
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: n1
real(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=sp), intent(inout) :: d(n)
real(kind=sp), intent(inout) :: sva(n)
integer(kind=ilp), intent(in) :: mv
real(kind=sp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=sp), intent(in) :: eps
real(kind=sp), intent(in) :: sfmin
real(kind=sp), intent(in) :: tol
integer(kind=ilp), intent(in) :: nsweep
real(kind=sp), intent(out) :: work(lwork)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

public pure subroutine zgsvj1(jobv, m, n, n1, a, lda, d, sva, mv, v, ldv, eps, sfmin, tol, nsweep, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobv
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: n1
complex(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=dp), intent(inout) :: d(n)
real(kind=dp), intent(inout) :: sva(n)
integer(kind=ilp), intent(in) :: mv
complex(kind=dp), intent(inout) :: v(ldv,*)
integer(kind=ilp), intent(in) :: ldv
real(kind=dp), intent(in) :: eps
real(kind=dp), intent(in) :: sfmin
real(kind=dp), intent(in) :: tol
integer(kind=ilp), intent(in) :: nsweep
complex(kind=dp), intent(out) :: work(lwork)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_cgsvj1()

Arguments

None

public interface stdlib_dgsvj1()

Arguments

None

public interface stdlib_sgsvj1()

Arguments

None

public interface stdlib_zgsvj1()

Arguments

None