File:  [local] / rpl / lapack / lapack / zlatdf.f
Revision 1.19: download - view: text, annotated - select for diffs - revision graph
Thu May 21 21:46:09 2020 UTC (3 years, 11 months ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_33, rpl-4_1_32, HEAD
Mise à jour de Lapack.

    1: *> \brief \b ZLATDF uses the LU factorization of the n-by-n matrix computed by sgetc2 and computes a contribution to the reciprocal Dif-estimate.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLATDF + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlatdf.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlatdf.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlatdf.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE ZLATDF( IJOB, N, Z, LDZ, RHS, RDSUM, RDSCAL, IPIV,
   22: *                          JPIV )
   23: *
   24: *       .. Scalar Arguments ..
   25: *       INTEGER            IJOB, LDZ, N
   26: *       DOUBLE PRECISION   RDSCAL, RDSUM
   27: *       ..
   28: *       .. Array Arguments ..
   29: *       INTEGER            IPIV( * ), JPIV( * )
   30: *       COMPLEX*16         RHS( * ), Z( LDZ, * )
   31: *       ..
   32: *
   33: *
   34: *> \par Purpose:
   35: *  =============
   36: *>
   37: *> \verbatim
   38: *>
   39: *> ZLATDF computes the contribution to the reciprocal Dif-estimate
   40: *> by solving for x in Z * x = b, where b is chosen such that the norm
   41: *> of x is as large as possible. It is assumed that LU decomposition
   42: *> of Z has been computed by ZGETC2. On entry RHS = f holds the
   43: *> contribution from earlier solved sub-systems, and on return RHS = x.
   44: *>
   45: *> The factorization of Z returned by ZGETC2 has the form
   46: *> Z = P * L * U * Q, where P and Q are permutation matrices. L is lower
   47: *> triangular with unit diagonal elements and U is upper triangular.
   48: *> \endverbatim
   49: *
   50: *  Arguments:
   51: *  ==========
   52: *
   53: *> \param[in] IJOB
   54: *> \verbatim
   55: *>          IJOB is INTEGER
   56: *>          IJOB = 2: First compute an approximative null-vector e
   57: *>              of Z using ZGECON, e is normalized and solve for
   58: *>              Zx = +-e - f with the sign giving the greater value of
   59: *>              2-norm(x).  About 5 times as expensive as Default.
   60: *>          IJOB .ne. 2: Local look ahead strategy where
   61: *>              all entries of the r.h.s. b is chosen as either +1 or
   62: *>              -1.  Default.
   63: *> \endverbatim
   64: *>
   65: *> \param[in] N
   66: *> \verbatim
   67: *>          N is INTEGER
   68: *>          The number of columns of the matrix Z.
   69: *> \endverbatim
   70: *>
   71: *> \param[in] Z
   72: *> \verbatim
   73: *>          Z is COMPLEX*16 array, dimension (LDZ, N)
   74: *>          On entry, the LU part of the factorization of the n-by-n
   75: *>          matrix Z computed by ZGETC2:  Z = P * L * U * Q
   76: *> \endverbatim
   77: *>
   78: *> \param[in] LDZ
   79: *> \verbatim
   80: *>          LDZ is INTEGER
   81: *>          The leading dimension of the array Z.  LDA >= max(1, N).
   82: *> \endverbatim
   83: *>
   84: *> \param[in,out] RHS
   85: *> \verbatim
   86: *>          RHS is COMPLEX*16 array, dimension (N).
   87: *>          On entry, RHS contains contributions from other subsystems.
   88: *>          On exit, RHS contains the solution of the subsystem with
   89: *>          entries according to the value of IJOB (see above).
   90: *> \endverbatim
   91: *>
   92: *> \param[in,out] RDSUM
   93: *> \verbatim
   94: *>          RDSUM is DOUBLE PRECISION
   95: *>          On entry, the sum of squares of computed contributions to
   96: *>          the Dif-estimate under computation by ZTGSYL, where the
   97: *>          scaling factor RDSCAL (see below) has been factored out.
   98: *>          On exit, the corresponding sum of squares updated with the
   99: *>          contributions from the current sub-system.
  100: *>          If TRANS = 'T' RDSUM is not touched.
  101: *>          NOTE: RDSUM only makes sense when ZTGSY2 is called by CTGSYL.
  102: *> \endverbatim
  103: *>
  104: *> \param[in,out] RDSCAL
  105: *> \verbatim
  106: *>          RDSCAL is DOUBLE PRECISION
  107: *>          On entry, scaling factor used to prevent overflow in RDSUM.
  108: *>          On exit, RDSCAL is updated w.r.t. the current contributions
  109: *>          in RDSUM.
  110: *>          If TRANS = 'T', RDSCAL is not touched.
  111: *>          NOTE: RDSCAL only makes sense when ZTGSY2 is called by
  112: *>          ZTGSYL.
  113: *> \endverbatim
  114: *>
  115: *> \param[in] IPIV
  116: *> \verbatim
  117: *>          IPIV is INTEGER array, dimension (N).
  118: *>          The pivot indices; for 1 <= i <= N, row i of the
  119: *>          matrix has been interchanged with row IPIV(i).
  120: *> \endverbatim
  121: *>
  122: *> \param[in] JPIV
  123: *> \verbatim
  124: *>          JPIV is INTEGER array, dimension (N).
  125: *>          The pivot indices; for 1 <= j <= N, column j of the
  126: *>          matrix has been interchanged with column JPIV(j).
  127: *> \endverbatim
  128: *
  129: *  Authors:
  130: *  ========
  131: *
  132: *> \author Univ. of Tennessee
  133: *> \author Univ. of California Berkeley
  134: *> \author Univ. of Colorado Denver
  135: *> \author NAG Ltd.
  136: *
  137: *> \date June 2016
  138: *
  139: *> \ingroup complex16OTHERauxiliary
  140: *
  141: *> \par Further Details:
  142: *  =====================
  143: *>
  144: *>  This routine is a further developed implementation of algorithm
  145: *>  BSOLVE in [1] using complete pivoting in the LU factorization.
  146: *
  147: *> \par Contributors:
  148: *  ==================
  149: *>
  150: *>     Bo Kagstrom and Peter Poromaa, Department of Computing Science,
  151: *>     Umea University, S-901 87 Umea, Sweden.
  152: *
  153: *> \par References:
  154: *  ================
  155: *>
  156: *>   [1]   Bo Kagstrom and Lars Westin,
  157: *>         Generalized Schur Methods with Condition Estimators for
  158: *>         Solving the Generalized Sylvester Equation, IEEE Transactions
  159: *>         on Automatic Control, Vol. 34, No. 7, July 1989, pp 745-751.
  160: *>\n
  161: *>   [2]   Peter Poromaa,
  162: *>         On Efficient and Robust Estimators for the Separation
  163: *>         between two Regular Matrix Pairs with Applications in
  164: *>         Condition Estimation. Report UMINF-95.05, Department of
  165: *>         Computing Science, Umea University, S-901 87 Umea, Sweden,
  166: *>         1995.
  167: *
  168: *  =====================================================================
  169:       SUBROUTINE ZLATDF( IJOB, N, Z, LDZ, RHS, RDSUM, RDSCAL, IPIV,
  170:      $                   JPIV )
  171: *
  172: *  -- LAPACK auxiliary routine (version 3.7.0) --
  173: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  174: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  175: *     June 2016
  176: *
  177: *     .. Scalar Arguments ..
  178:       INTEGER            IJOB, LDZ, N
  179:       DOUBLE PRECISION   RDSCAL, RDSUM
  180: *     ..
  181: *     .. Array Arguments ..
  182:       INTEGER            IPIV( * ), JPIV( * )
  183:       COMPLEX*16         RHS( * ), Z( LDZ, * )
  184: *     ..
  185: *
  186: *  =====================================================================
  187: *
  188: *     .. Parameters ..
  189:       INTEGER            MAXDIM
  190:       PARAMETER          ( MAXDIM = 2 )
  191:       DOUBLE PRECISION   ZERO, ONE
  192:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
  193:       COMPLEX*16         CONE
  194:       PARAMETER          ( CONE = ( 1.0D+0, 0.0D+0 ) )
  195: *     ..
  196: *     .. Local Scalars ..
  197:       INTEGER            I, INFO, J, K
  198:       DOUBLE PRECISION   RTEMP, SCALE, SMINU, SPLUS
  199:       COMPLEX*16         BM, BP, PMONE, TEMP
  200: *     ..
  201: *     .. Local Arrays ..
  202:       DOUBLE PRECISION   RWORK( MAXDIM )
  203:       COMPLEX*16         WORK( 4*MAXDIM ), XM( MAXDIM ), XP( MAXDIM )
  204: *     ..
  205: *     .. External Subroutines ..
  206:       EXTERNAL           ZAXPY, ZCOPY, ZGECON, ZGESC2, ZLASSQ, ZLASWP,
  207:      $                   ZSCAL
  208: *     ..
  209: *     .. External Functions ..
  210:       DOUBLE PRECISION   DZASUM
  211:       COMPLEX*16         ZDOTC
  212:       EXTERNAL           DZASUM, ZDOTC
  213: *     ..
  214: *     .. Intrinsic Functions ..
  215:       INTRINSIC          ABS, DBLE, SQRT
  216: *     ..
  217: *     .. Executable Statements ..
  218: *
  219:       IF( IJOB.NE.2 ) THEN
  220: *
  221: *        Apply permutations IPIV to RHS
  222: *
  223:          CALL ZLASWP( 1, RHS, LDZ, 1, N-1, IPIV, 1 )
  224: *
  225: *        Solve for L-part choosing RHS either to +1 or -1.
  226: *
  227:          PMONE = -CONE
  228:          DO 10 J = 1, N - 1
  229:             BP = RHS( J ) + CONE
  230:             BM = RHS( J ) - CONE
  231:             SPLUS = ONE
  232: *
  233: *           Lockahead for L- part RHS(1:N-1) = +-1
  234: *           SPLUS and SMIN computed more efficiently than in BSOLVE[1].
  235: *
  236:             SPLUS = SPLUS + DBLE( ZDOTC( N-J, Z( J+1, J ), 1, Z( J+1,
  237:      $              J ), 1 ) )
  238:             SMINU = DBLE( ZDOTC( N-J, Z( J+1, J ), 1, RHS( J+1 ), 1 ) )
  239:             SPLUS = SPLUS*DBLE( RHS( J ) )
  240:             IF( SPLUS.GT.SMINU ) THEN
  241:                RHS( J ) = BP
  242:             ELSE IF( SMINU.GT.SPLUS ) THEN
  243:                RHS( J ) = BM
  244:             ELSE
  245: *
  246: *              In this case the updating sums are equal and we can
  247: *              choose RHS(J) +1 or -1. The first time this happens we
  248: *              choose -1, thereafter +1. This is a simple way to get
  249: *              good estimates of matrices like Byers well-known example
  250: *              (see [1]). (Not done in BSOLVE.)
  251: *
  252:                RHS( J ) = RHS( J ) + PMONE
  253:                PMONE = CONE
  254:             END IF
  255: *
  256: *           Compute the remaining r.h.s.
  257: *
  258:             TEMP = -RHS( J )
  259:             CALL ZAXPY( N-J, TEMP, Z( J+1, J ), 1, RHS( J+1 ), 1 )
  260:    10    CONTINUE
  261: *
  262: *        Solve for U- part, lockahead for RHS(N) = +-1. This is not done
  263: *        In BSOLVE and will hopefully give us a better estimate because
  264: *        any ill-conditioning of the original matrix is transferred to U
  265: *        and not to L. U(N, N) is an approximation to sigma_min(LU).
  266: *
  267:          CALL ZCOPY( N-1, RHS, 1, WORK, 1 )
  268:          WORK( N ) = RHS( N ) + CONE
  269:          RHS( N ) = RHS( N ) - CONE
  270:          SPLUS = ZERO
  271:          SMINU = ZERO
  272:          DO 30 I = N, 1, -1
  273:             TEMP = CONE / Z( I, I )
  274:             WORK( I ) = WORK( I )*TEMP
  275:             RHS( I ) = RHS( I )*TEMP
  276:             DO 20 K = I + 1, N
  277:                WORK( I ) = WORK( I ) - WORK( K )*( Z( I, K )*TEMP )
  278:                RHS( I ) = RHS( I ) - RHS( K )*( Z( I, K )*TEMP )
  279:    20       CONTINUE
  280:             SPLUS = SPLUS + ABS( WORK( I ) )
  281:             SMINU = SMINU + ABS( RHS( I ) )
  282:    30    CONTINUE
  283:          IF( SPLUS.GT.SMINU )
  284:      $      CALL ZCOPY( N, WORK, 1, RHS, 1 )
  285: *
  286: *        Apply the permutations JPIV to the computed solution (RHS)
  287: *
  288:          CALL ZLASWP( 1, RHS, LDZ, 1, N-1, JPIV, -1 )
  289: *
  290: *        Compute the sum of squares
  291: *
  292:          CALL ZLASSQ( N, RHS, 1, RDSCAL, RDSUM )
  293:          RETURN
  294:       END IF
  295: *
  296: *     ENTRY IJOB = 2
  297: *
  298: *     Compute approximate nullvector XM of Z
  299: *
  300:       CALL ZGECON( 'I', N, Z, LDZ, ONE, RTEMP, WORK, RWORK, INFO )
  301:       CALL ZCOPY( N, WORK( N+1 ), 1, XM, 1 )
  302: *
  303: *     Compute RHS
  304: *
  305:       CALL ZLASWP( 1, XM, LDZ, 1, N-1, IPIV, -1 )
  306:       TEMP = CONE / SQRT( ZDOTC( N, XM, 1, XM, 1 ) )
  307:       CALL ZSCAL( N, TEMP, XM, 1 )
  308:       CALL ZCOPY( N, XM, 1, XP, 1 )
  309:       CALL ZAXPY( N, CONE, RHS, 1, XP, 1 )
  310:       CALL ZAXPY( N, -CONE, XM, 1, RHS, 1 )
  311:       CALL ZGESC2( N, Z, LDZ, RHS, IPIV, JPIV, SCALE )
  312:       CALL ZGESC2( N, Z, LDZ, XP, IPIV, JPIV, SCALE )
  313:       IF( DZASUM( N, XP, 1 ).GT.DZASUM( N, RHS, 1 ) )
  314:      $   CALL ZCOPY( N, XP, 1, RHS, 1 )
  315: *
  316: *     Compute the sum of squares
  317: *
  318:       CALL ZLASSQ( N, RHS, 1, RDSCAL, RDSUM )
  319:       RETURN
  320: *
  321: *     End of ZLATDF
  322: *
  323:       END

CVSweb interface <joel.bertrand@systella.fr>