Diff for /rpl/lapack/lapack/zgbequb.f between versions 1.4 and 1.5

version 1.4, 2010/12/21 13:53:42 version 1.5, 2011/11/21 20:43:08
Line 1 Line 1
   *> \brief \b ZGBEQUB
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download ZGBEQUB + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgbequb.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgbequb.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgbequb.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE ZGBEQUB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
   *                           AMAX, INFO )
   * 
   *       .. Scalar Arguments ..
   *       INTEGER            INFO, KL, KU, LDAB, M, N
   *       DOUBLE PRECISION   AMAX, COLCND, ROWCND
   *       ..
   *       .. Array Arguments ..
   *       DOUBLE PRECISION   C( * ), R( * )
   *       COMPLEX*16         AB( LDAB, * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> ZGBEQUB computes row and column scalings intended to equilibrate an
   *> M-by-N matrix A and reduce its condition number.  R returns the row
   *> scale factors and C the column scale factors, chosen to try to make
   *> the largest element in each row and column of the matrix B with
   *> elements B(i,j)=R(i)*A(i,j)*C(j) have an absolute value of at most
   *> the radix.
   *>
   *> R(i) and C(j) are restricted to be a power of the radix between
   *> SMLNUM = smallest safe number and BIGNUM = largest safe number.  Use
   *> of these scaling factors is not guaranteed to reduce the condition
   *> number of A but works well in practice.
   *>
   *> This routine differs from ZGEEQU by restricting the scaling factors
   *> to a power of the radix.  Baring over- and underflow, scaling by
   *> these factors introduces no additional rounding errors.  However, the
   *> scaled entries' magnitured are no longer approximately 1 but lie
   *> between sqrt(radix) and 1/sqrt(radix).
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] M
   *> \verbatim
   *>          M is INTEGER
   *>          The number of rows of the matrix A.  M >= 0.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>          The number of columns of the matrix A.  N >= 0.
   *> \endverbatim
   *>
   *> \param[in] KL
   *> \verbatim
   *>          KL is INTEGER
   *>          The number of subdiagonals within the band of A.  KL >= 0.
   *> \endverbatim
   *>
   *> \param[in] KU
   *> \verbatim
   *>          KU is INTEGER
   *>          The number of superdiagonals within the band of A.  KU >= 0.
   *> \endverbatim
   *>
   *> \param[in] AB
   *> \verbatim
   *>          AB is DOUBLE PRECISION array, dimension (LDAB,N)
   *>          On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
   *>          The j-th column of A is stored in the j-th column of the
   *>          array AB as follows:
   *>          AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
   *> \endverbatim
   *>
   *> \param[in] LDAB
   *> \verbatim
   *>          LDAB is INTEGER
   *>          The leading dimension of the array A.  LDAB >= max(1,M).
   *> \endverbatim
   *>
   *> \param[out] R
   *> \verbatim
   *>          R is DOUBLE PRECISION array, dimension (M)
   *>          If INFO = 0 or INFO > M, R contains the row scale factors
   *>          for A.
   *> \endverbatim
   *>
   *> \param[out] C
   *> \verbatim
   *>          C is DOUBLE PRECISION array, dimension (N)
   *>          If INFO = 0,  C contains the column scale factors for A.
   *> \endverbatim
   *>
   *> \param[out] ROWCND
   *> \verbatim
   *>          ROWCND is DOUBLE PRECISION
   *>          If INFO = 0 or INFO > M, ROWCND contains the ratio of the
   *>          smallest R(i) to the largest R(i).  If ROWCND >= 0.1 and
   *>          AMAX is neither too large nor too small, it is not worth
   *>          scaling by R.
   *> \endverbatim
   *>
   *> \param[out] COLCND
   *> \verbatim
   *>          COLCND is DOUBLE PRECISION
   *>          If INFO = 0, COLCND contains the ratio of the smallest
   *>          C(i) to the largest C(i).  If COLCND >= 0.1, it is not
   *>          worth scaling by C.
   *> \endverbatim
   *>
   *> \param[out] AMAX
   *> \verbatim
   *>          AMAX is DOUBLE PRECISION
   *>          Absolute value of largest matrix element.  If AMAX is very
   *>          close to overflow or very close to underflow, the matrix
   *>          should be scaled.
   *> \endverbatim
   *>
   *> \param[out] INFO
   *> \verbatim
   *>          INFO is INTEGER
   *>          = 0:  successful exit
   *>          < 0:  if INFO = -i, the i-th argument had an illegal value
   *>          > 0:  if INFO = i,  and i is
   *>                <= M:  the i-th row of A is exactly zero
   *>                >  M:  the (i-M)-th column of A is exactly zero
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup complex16GBcomputational
   *
   *  =====================================================================
       SUBROUTINE ZGBEQUB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,        SUBROUTINE ZGBEQUB( M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND,
      $                    AMAX, INFO )       $                    AMAX, INFO )
 *  *
 *     -- LAPACK routine (version 3.2)                                 --  *  -- LAPACK computational routine (version 3.4.0) --
 *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *     -- Jason Riedy of Univ. of California Berkeley.                 --  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     -- November 2008                                                --  *     November 2011
 *  
 *     -- LAPACK is a software package provided by Univ. of Tennessee, --  
 *     -- Univ. of California Berkeley and NAG Ltd.                    --  
 *  *
       IMPLICIT NONE  
 *     ..  
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            INFO, KL, KU, LDAB, M, N        INTEGER            INFO, KL, KU, LDAB, M, N
       DOUBLE PRECISION   AMAX, COLCND, ROWCND        DOUBLE PRECISION   AMAX, COLCND, ROWCND
Line 20 Line 175
       COMPLEX*16         AB( LDAB, * )        COMPLEX*16         AB( LDAB, * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  ZGBEQUB computes row and column scalings intended to equilibrate an  
 *  M-by-N matrix A and reduce its condition number.  R returns the row  
 *  scale factors and C the column scale factors, chosen to try to make  
 *  the largest element in each row and column of the matrix B with  
 *  elements B(i,j)=R(i)*A(i,j)*C(j) have an absolute value of at most  
 *  the radix.  
 *  
 *  R(i) and C(j) are restricted to be a power of the radix between  
 *  SMLNUM = smallest safe number and BIGNUM = largest safe number.  Use  
 *  of these scaling factors is not guaranteed to reduce the condition  
 *  number of A but works well in practice.  
 *  
 *  This routine differs from ZGEEQU by restricting the scaling factors  
 *  to a power of the radix.  Baring over- and underflow, scaling by  
 *  these factors introduces no additional rounding errors.  However, the  
 *  scaled entries' magnitured are no longer approximately 1 but lie  
 *  between sqrt(radix) and 1/sqrt(radix).  
 *  
 *  Arguments  
 *  =========  
 *  
 *  M       (input) INTEGER  
 *          The number of rows of the matrix A.  M >= 0.  
 *  
 *  N       (input) INTEGER  
 *          The number of columns of the matrix A.  N >= 0.  
 *  
 *  KL      (input) INTEGER  
 *          The number of subdiagonals within the band of A.  KL >= 0.  
 *  
 *  KU      (input) INTEGER  
 *          The number of superdiagonals within the band of A.  KU >= 0.  
 *  
 *  AB      (input) DOUBLE PRECISION array, dimension (LDAB,N)  
 *          On entry, the matrix A in band storage, in rows 1 to KL+KU+1.  
 *          The j-th column of A is stored in the j-th column of the  
 *          array AB as follows:  
 *          AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)  
 *  
 *  LDAB    (input) INTEGER  
 *          The leading dimension of the array A.  LDAB >= max(1,M).  
 *  
 *  R       (output) DOUBLE PRECISION array, dimension (M)  
 *          If INFO = 0 or INFO > M, R contains the row scale factors  
 *          for A.  
 *  
 *  C       (output) DOUBLE PRECISION array, dimension (N)  
 *          If INFO = 0,  C contains the column scale factors for A.  
 *  
 *  ROWCND  (output) DOUBLE PRECISION  
 *          If INFO = 0 or INFO > M, ROWCND contains the ratio of the  
 *          smallest R(i) to the largest R(i).  If ROWCND >= 0.1 and  
 *          AMAX is neither too large nor too small, it is not worth  
 *          scaling by R.  
 *  
 *  COLCND  (output) DOUBLE PRECISION  
 *          If INFO = 0, COLCND contains the ratio of the smallest  
 *          C(i) to the largest C(i).  If COLCND >= 0.1, it is not  
 *          worth scaling by C.  
 *  
 *  AMAX    (output) DOUBLE PRECISION  
 *          Absolute value of largest matrix element.  If AMAX is very  
 *          close to overflow or very close to underflow, the matrix  
 *          should be scaled.  
 *  
 *  INFO    (output) INTEGER  
 *          = 0:  successful exit  
 *          < 0:  if INFO = -i, the i-th argument had an illegal value  
 *          > 0:  if INFO = i,  and i is  
 *                <= M:  the i-th row of A is exactly zero  
 *                >  M:  the (i-M)-th column of A is exactly zero  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..

Removed from v.1.4  
changed lines
  Added in v.1.5


CVSweb interface <joel.bertrand@systella.fr>