stdlib_linalg_lapack_aux Module



Abstract Interfaces

abstract interface

  • public pure function stdlib_selctg_c(alpha, beta)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: alpha
    complex(kind=sp), intent(in) :: beta

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_selctg_d(alphar, alphai, beta)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: alphar
    real(kind=dp), intent(in) :: alphai
    real(kind=dp), intent(in) :: beta

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_selctg_s(alphar, alphai, beta)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: alphar
    real(kind=sp), intent(in) :: alphai
    real(kind=sp), intent(in) :: beta

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_selctg_z(alpha, beta)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: alpha
    complex(kind=dp), intent(in) :: beta

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_select_c(alpha)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: alpha

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_select_d(alphar, alphai)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: alphar
    real(kind=dp), intent(in) :: alphai

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_select_s(alphar, alphai)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: alphar
    real(kind=sp), intent(in) :: alphai

    Return Value logical(kind=lk)

abstract interface

  • public pure function stdlib_select_z(alpha)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: alpha

    Return Value logical(kind=lk)


Functions

public pure function stdlib_chla_transtype(trans)

This subroutine translates from a BLAST-specified integer constant to the character string specifying a transposition operation. CHLA_TRANSTYPE returns an CHARACTER*1. If CHLA_TRANSTYPE: is 'X', then input is not an integer indicating a transposition operator. Otherwise CHLA_TRANSTYPE returns the constant value corresponding to TRANS.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: trans

Return Value character(len=1)

public pure function stdlib_droundup_lwork(lwork)

ROUNDUP_LWORK >= LWORK. ROUNDUP_LWORK is guaranteed to have zero decimal part.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: lwork

Return Value real(kind=dp)

public pure function stdlib_icmax1(n, zx, incx)

IMAX1: finds the index of the first vector element of maximum absolute value. Based on IAMAX from Level 1 BLAS. The change is to use the 'genuine' absolute value.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(in) :: zx(*)
integer(kind=ilp), intent(in) :: incx

Return Value integer(kind=ilp)

public pure function stdlib_ieeeck(ispec, zero, one)

IEEECK is called from the ILAENV to verify that Infinity and possibly NaN arithmetic is safe (i.e. will not trap).

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: ispec
real(kind=sp), intent(in) :: zero
real(kind=sp), intent(in) :: one

Return Value integer(kind=ilp)

public pure function stdlib_ilaclc(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public pure function stdlib_ilaclr(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public function stdlib_iladiag(diag)

This subroutine translated from a character string specifying if a matrix has unit diagonal or not to the relevant BLAST-specified integer constant. ILADIAG returns an INTEGER. If ILADIAG: < 0, then the input is not a character indicating a unit or non-unit diagonal. Otherwise ILADIAG returns the constant value corresponding to DIAG.

Arguments

Type IntentOptional Attributes Name
character(len=1) :: diag

Return Value integer(kind=ilp)

public pure function stdlib_iladlc(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public pure function stdlib_iladlr(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public pure function stdlib_ilaenv(ispec, name, opts, n1, n2, n3, n4)

ILAENV is called from the LAPACK routines to choose problem-dependent parameters for the local environment. See ISPEC for a description of the parameters. ILAENV returns an INTEGER if ILAENV >= 0: ILAENV returns the value of the parameter specified by ISPEC if ILAENV < 0: if ILAENV = -k, the k-th argument had an illegal value. This version provides a set of parameters which should give good, but not optimal, performance on many of the currently available computers. Users are encouraged to modify this subroutine to set the tuning parameters for their particular machine using the option and problem size information in the arguments. This routine will not function correctly if it is converted to all lower case. Converting it to all upper case is allowed.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: ispec
character(len=*), intent(in) :: name
character(len=*), intent(in) :: opts
integer(kind=ilp), intent(in) :: n1
integer(kind=ilp), intent(in) :: n2
integer(kind=ilp), intent(in) :: n3
integer(kind=ilp), intent(in) :: n4

Return Value integer(kind=ilp)

public function stdlib_ilaenv2stage(ispec, name, opts, n1, n2, n3, n4)

ILAENV2STAGE is called from the LAPACK routines to choose problem-dependent parameters for the local environment. See ISPEC for a description of the parameters. It sets problem and machine dependent parameters useful for *_2STAGE and related subroutines. ILAENV2STAGE returns an INTEGER if ILAENV2STAGE >= 0: ILAENV2STAGE returns the value of the parameter specified by ISPEC if ILAENV2STAGE < 0: if ILAENV2STAGE = -k, the k-th argument had an illegal value. This version provides a set of parameters which should give good, but not optimal, performance on many of the currently available computers for the 2-stage solvers. Users are encouraged to modify this subroutine to set the tuning parameters for their particular machine using the option and problem size information in the arguments. This routine will not function correctly if it is converted to all lower case. Converting it to all upper case is allowed.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: ispec
character(len=*), intent(in) :: name
character(len=*), intent(in) :: opts
integer(kind=ilp), intent(in) :: n1
integer(kind=ilp), intent(in) :: n2
integer(kind=ilp), intent(in) :: n3
integer(kind=ilp), intent(in) :: n4

Return Value integer(kind=ilp)

public function stdlib_ilaprec(prec)

This subroutine translated from a character string specifying an intermediate precision to the relevant BLAST-specified integer constant. ILAPREC returns an INTEGER. If ILAPREC: < 0, then the input is not a character indicating a supported intermediate precision. Otherwise ILAPREC returns the constant value corresponding to PREC.

Arguments

Type IntentOptional Attributes Name
character(len=1) :: prec

Return Value integer(kind=ilp)

public pure function stdlib_ilaslc(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public pure function stdlib_ilaslr(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public function stdlib_ilatrans(trans)

This subroutine translates from a character string specifying a transposition operation to the relevant BLAST-specified integer constant. ILATRANS returns an INTEGER. If ILATRANS: < 0, then the input is not a character indicating a transposition operator. Otherwise ILATRANS returns the constant value corresponding to TRANS.

Arguments

Type IntentOptional Attributes Name
character(len=1) :: trans

Return Value integer(kind=ilp)

public function stdlib_ilauplo(uplo)

This subroutine translated from a character string specifying a upper- or lower-triangular matrix to the relevant BLAST-specified integer constant. ILAUPLO returns an INTEGER. If ILAUPLO: < 0, then the input is not a character indicating an upper- or lower-triangular matrix. Otherwise ILAUPLO returns the constant value corresponding to UPLO.

Arguments

Type IntentOptional Attributes Name
character(len=1) :: uplo

Return Value integer(kind=ilp)

public pure function stdlib_ilazlc(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public pure function stdlib_ilazlr(m, n, a, lda)

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda

Return Value integer(kind=ilp)

public function stdlib_iparam2stage(ispec, name, opts, ni, nbi, ibi, nxi)

This program sets problem and machine dependent parameters useful for xHETRD_2STAGE, xHETRD_HE2HB, xHETRD_HB2ST, xGEBRD_2STAGE, xGEBRD_GE2GB, xGEBRD_GB2BD and related subroutines for eigenvalue problems. It is called whenever ILAENV is called with 17 <= ISPEC <= 21. It is called whenever ILAENV2STAGE is called with 1 <= ISPEC <= 5 with a direct conversion ISPEC + 16.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: ispec
character(len=*), intent(in) :: name
character(len=*), intent(in) :: opts
integer(kind=ilp), intent(in) :: ni
integer(kind=ilp), intent(in) :: nbi
integer(kind=ilp), intent(in) :: ibi
integer(kind=ilp), intent(in) :: nxi

Return Value integer(kind=ilp)

public pure function stdlib_iparmq(ispec, name, opts, n, ilo, ihi, lwork)

This program sets problem and machine dependent parameters useful for xHSEQR and related subroutines for eigenvalue problems. It is called whenever IPARMQ is called with 12 <= ISPEC <= 16

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: ispec
character(len=1), intent(in) :: name*(*)
character(len=1), intent(in) :: opts*(*)
integer(kind=ilp), intent(in) :: n
integer(kind=ilp), intent(in) :: ilo
integer(kind=ilp), intent(in) :: ihi
integer(kind=ilp), intent(in) :: lwork

Return Value integer(kind=ilp)

public pure function stdlib_izmax1(n, zx, incx)

IMAX1: finds the index of the first vector element of maximum absolute value. Based on IAMAX from Level 1 BLAS. The change is to use the 'genuine' absolute value.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(in) :: zx(*)
integer(kind=ilp), intent(in) :: incx

Return Value integer(kind=ilp)

public pure function stdlib_lsamen(n, ca, cb)

LSAMEN tests if the first N letters of CA are the same as the first N letters of CB, regardless of case. LSAMEN returns .TRUE. if CA and CB are equivalent except for case and .FALSE. otherwise. LSAMEN also returns .FALSE. if LEN( CA ) or LEN( CB ) is less than N.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
character(len=*), intent(in) :: ca
character(len=*), intent(in) :: cb

Return Value logical(kind=lk)

public pure function stdlib_sroundup_lwork(lwork)

ROUNDUP_LWORK >= LWORK. ROUNDUP_LWORK is guaranteed to have zero decimal part.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: lwork

Return Value real(kind=sp)