Diff for /rpl/lapack/lapack/dlaed3.f between versions 1.7 and 1.8

version 1.7, 2010/12/21 13:53:29 version 1.8, 2011/11/21 20:42:54
Line 1 Line 1
   *> \brief \b DLAED3
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download DLAED3 + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaed3.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaed3.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed3.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
   *                          CTOT, W, S, INFO )
   * 
   *       .. Scalar Arguments ..
   *       INTEGER            INFO, K, LDQ, N, N1
   *       DOUBLE PRECISION   RHO
   *       ..
   *       .. Array Arguments ..
   *       INTEGER            CTOT( * ), INDX( * )
   *       DOUBLE PRECISION   D( * ), DLAMDA( * ), Q( LDQ, * ), Q2( * ),
   *      $                   S( * ), W( * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> DLAED3 finds the roots of the secular equation, as defined by the
   *> values in D, W, and RHO, between 1 and K.  It makes the
   *> appropriate calls to DLAED4 and then updates the eigenvectors by
   *> multiplying the matrix of eigenvectors of the pair of eigensystems
   *> being combined by the matrix of eigenvectors of the K-by-K system
   *> which is solved here.
   *>
   *> This code makes very mild assumptions about floating point
   *> arithmetic. It will work on machines with a guard digit in
   *> add/subtract, or on those binary machines without guard digits
   *> which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2.
   *> It could conceivably fail on hexadecimal or decimal machines
   *> without guard digits, but we know of none.
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] K
   *> \verbatim
   *>          K is INTEGER
   *>          The number of terms in the rational function to be solved by
   *>          DLAED4.  K >= 0.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>          The number of rows and columns in the Q matrix.
   *>          N >= K (deflation may result in N>K).
   *> \endverbatim
   *>
   *> \param[in] N1
   *> \verbatim
   *>          N1 is INTEGER
   *>          The location of the last eigenvalue in the leading submatrix.
   *>          min(1,N) <= N1 <= N/2.
   *> \endverbatim
   *>
   *> \param[out] D
   *> \verbatim
   *>          D is DOUBLE PRECISION array, dimension (N)
   *>          D(I) contains the updated eigenvalues for
   *>          1 <= I <= K.
   *> \endverbatim
   *>
   *> \param[out] Q
   *> \verbatim
   *>          Q is DOUBLE PRECISION array, dimension (LDQ,N)
   *>          Initially the first K columns are used as workspace.
   *>          On output the columns 1 to K contain
   *>          the updated eigenvectors.
   *> \endverbatim
   *>
   *> \param[in] LDQ
   *> \verbatim
   *>          LDQ is INTEGER
   *>          The leading dimension of the array Q.  LDQ >= max(1,N).
   *> \endverbatim
   *>
   *> \param[in] RHO
   *> \verbatim
   *>          RHO is DOUBLE PRECISION
   *>          The value of the parameter in the rank one update equation.
   *>          RHO >= 0 required.
   *> \endverbatim
   *>
   *> \param[in,out] DLAMDA
   *> \verbatim
   *>          DLAMDA is DOUBLE PRECISION array, dimension (K)
   *>          The first K elements of this array contain the old roots
   *>          of the deflated updating problem.  These are the poles
   *>          of the secular equation. May be changed on output by
   *>          having lowest order bit set to zero on Cray X-MP, Cray Y-MP,
   *>          Cray-2, or Cray C-90, as described above.
   *> \endverbatim
   *>
   *> \param[in] Q2
   *> \verbatim
   *>          Q2 is DOUBLE PRECISION array, dimension (LDQ2, N)
   *>          The first K columns of this matrix contain the non-deflated
   *>          eigenvectors for the split problem.
   *> \endverbatim
   *>
   *> \param[in] INDX
   *> \verbatim
   *>          INDX is INTEGER array, dimension (N)
   *>          The permutation used to arrange the columns of the deflated
   *>          Q matrix into three groups (see DLAED2).
   *>          The rows of the eigenvectors found by DLAED4 must be likewise
   *>          permuted before the matrix multiply can take place.
   *> \endverbatim
   *>
   *> \param[in] CTOT
   *> \verbatim
   *>          CTOT is INTEGER array, dimension (4)
   *>          A count of the total number of the various types of columns
   *>          in Q, as described in INDX.  The fourth column type is any
   *>          column which has been deflated.
   *> \endverbatim
   *>
   *> \param[in,out] W
   *> \verbatim
   *>          W is DOUBLE PRECISION array, dimension (K)
   *>          The first K elements of this array contain the components
   *>          of the deflation-adjusted updating vector. Destroyed on
   *>          output.
   *> \endverbatim
   *>
   *> \param[out] S
   *> \verbatim
   *>          S is DOUBLE PRECISION array, dimension (N1 + 1)*K
   *>          Will contain the eigenvectors of the repaired matrix which
   *>          will be multiplied by the previously accumulated eigenvectors
   *>          to update the system.
   *> \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 = 1, an eigenvalue did not converge
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup auxOTHERcomputational
   *
   *> \par Contributors:
   *  ==================
   *>
   *> Jeff Rutter, Computer Science Division, University of California
   *> at Berkeley, USA \n
   *>  Modified by Francoise Tisseur, University of Tennessee
   *>
   *  =====================================================================
       SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,        SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
      $                   CTOT, W, S, INFO )       $                   CTOT, W, S, INFO )
 *  *
 *  -- LAPACK routine (version 3.2) --  *  -- LAPACK computational routine (version 3.4.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     November 2006  *     November 2011
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            INFO, K, LDQ, N, N1        INTEGER            INFO, K, LDQ, N, N1
Line 16 Line 200
      $                   S( * ), W( * )       $                   S( * ), W( * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  DLAED3 finds the roots of the secular equation, as defined by the  
 *  values in D, W, and RHO, between 1 and K.  It makes the  
 *  appropriate calls to DLAED4 and then updates the eigenvectors by  
 *  multiplying the matrix of eigenvectors of the pair of eigensystems  
 *  being combined by the matrix of eigenvectors of the K-by-K system  
 *  which is solved here.  
 *  
 *  This code makes very mild assumptions about floating point  
 *  arithmetic. It will work on machines with a guard digit in  
 *  add/subtract, or on those binary machines without guard digits  
 *  which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2.  
 *  It could conceivably fail on hexadecimal or decimal machines  
 *  without guard digits, but we know of none.  
 *  
 *  Arguments  
 *  =========  
 *  
 *  K       (input) INTEGER  
 *          The number of terms in the rational function to be solved by  
 *          DLAED4.  K >= 0.  
 *  
 *  N       (input) INTEGER  
 *          The number of rows and columns in the Q matrix.  
 *          N >= K (deflation may result in N>K).  
 *  
 *  N1      (input) INTEGER  
 *          The location of the last eigenvalue in the leading submatrix.  
 *          min(1,N) <= N1 <= N/2.  
 *  
 *  D       (output) DOUBLE PRECISION array, dimension (N)  
 *          D(I) contains the updated eigenvalues for  
 *          1 <= I <= K.  
 *  
 *  Q       (output) DOUBLE PRECISION array, dimension (LDQ,N)  
 *          Initially the first K columns are used as workspace.  
 *          On output the columns 1 to K contain  
 *          the updated eigenvectors.  
 *  
 *  LDQ     (input) INTEGER  
 *          The leading dimension of the array Q.  LDQ >= max(1,N).  
 *  
 *  RHO     (input) DOUBLE PRECISION  
 *          The value of the parameter in the rank one update equation.  
 *          RHO >= 0 required.  
 *  
 *  DLAMDA  (input/output) DOUBLE PRECISION array, dimension (K)  
 *          The first K elements of this array contain the old roots  
 *          of the deflated updating problem.  These are the poles  
 *          of the secular equation. May be changed on output by  
 *          having lowest order bit set to zero on Cray X-MP, Cray Y-MP,  
 *          Cray-2, or Cray C-90, as described above.  
 *  
 *  Q2      (input) DOUBLE PRECISION array, dimension (LDQ2, N)  
 *          The first K columns of this matrix contain the non-deflated  
 *          eigenvectors for the split problem.  
 *  
 *  INDX    (input) INTEGER array, dimension (N)  
 *          The permutation used to arrange the columns of the deflated  
 *          Q matrix into three groups (see DLAED2).  
 *          The rows of the eigenvectors found by DLAED4 must be likewise  
 *          permuted before the matrix multiply can take place.  
 *  
 *  CTOT    (input) INTEGER array, dimension (4)  
 *          A count of the total number of the various types of columns  
 *          in Q, as described in INDX.  The fourth column type is any  
 *          column which has been deflated.  
 *  
 *  W       (input/output) DOUBLE PRECISION array, dimension (K)  
 *          The first K elements of this array contain the components  
 *          of the deflation-adjusted updating vector. Destroyed on  
 *          output.  
 *  
 *  S       (workspace) DOUBLE PRECISION array, dimension (N1 + 1)*K  
 *          Will contain the eigenvectors of the repaired matrix which  
 *          will be multiplied by the previously accumulated eigenvectors  
 *          to update the system.  
 *  
 *  LDS     (input) INTEGER  
 *          The leading dimension of S.  LDS >= max(1,K).  
 *  
 *  INFO    (output) INTEGER  
 *          = 0:  successful exit.  
 *          < 0:  if INFO = -i, the i-th argument had an illegal value.  
 *          > 0:  if INFO = 1, an eigenvalue did not converge  
 *  
 *  Further Details  
 *  ===============  
 *  
 *  Based on contributions by  
 *     Jeff Rutter, Computer Science Division, University of California  
 *     at Berkeley, USA  
 *  Modified by Francoise Tisseur, University of Tennessee.  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..

Removed from v.1.7  
changed lines
  Added in v.1.8


CVSweb interface <joel.bertrand@systella.fr>