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

version 1.7, 2010/12/21 13:53:45 version 1.8, 2011/07/22 07:38:14
Line 1 Line 1
       SUBROUTINE ZGGLSE( M, N, P, A, LDA, B, LDB, C, D, X, WORK, LWORK,        SUBROUTINE ZGGLSE( M, N, P, A, LDA, B, LDB, C, D, X, WORK, LWORK,
      $                   INFO )       $                   INFO )
 *  *
 *  -- LAPACK driver routine (version 3.2) --  *  -- LAPACK driver routine (version 3.3.1) --
 *  -- 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..--
 *     February 2007  *  -- April 2011                                                      --
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       INTEGER            INFO, LDA, LDB, LWORK, M, N, P        INTEGER            INFO, LDA, LDB, LWORK, M, N, P
Line 26 Line 26
 *  M-vector, and d is a given P-vector. It is assumed that  *  M-vector, and d is a given P-vector. It is assumed that
 *  P <= N <= M+P, and  *  P <= N <= M+P, and
 *  *
 *           rank(B) = P and  rank( ( A ) ) = N.  *           rank(B) = P and  rank( (A) ) = N.
 *                                ( ( B ) )  *                                ( (B) )
 *  *
 *  These conditions ensure that the LSE problem has a unique solution,  *  These conditions ensure that the LSE problem has a unique solution,
 *  which is obtained using a generalized RQ factorization of the  *  which is obtained using a generalized RQ factorization of the
Line 183 Line 183
 *  *
 *     Compute the GRQ factorization of matrices B and A:  *     Compute the GRQ factorization of matrices B and A:
 *  *
 *            B*Q' = (  0  T12 ) P   Z'*A*Q' = ( R11 R12 ) N-P  *            B*Q**H = (  0  T12 ) P   Z**H*A*Q**H = ( R11 R12 ) N-P
 *                     N-P  P                  (  0  R22 ) M+P-N  *                        N-P  P                     (  0  R22 ) M+P-N
 *                                               N-P  P  *                                                      N-P  P
 *  *
 *     where T12 and R11 are upper triangular, and Q and Z are  *     where T12 and R11 are upper triangular, and Q and Z are
 *     unitary.  *     unitary.
Line 194 Line 194
      $             WORK( P+MN+1 ), LWORK-P-MN, INFO )       $             WORK( P+MN+1 ), LWORK-P-MN, INFO )
       LOPT = WORK( P+MN+1 )        LOPT = WORK( P+MN+1 )
 *  *
 *     Update c = Z'*c = ( c1 ) N-P  *     Update c = Z**H *c = ( c1 ) N-P
 *                       ( c2 ) M+P-N  *                       ( c2 ) M+P-N
 *  *
       CALL ZUNMQR( 'Left', 'Conjugate Transpose', M, 1, MN, A, LDA,        CALL ZUNMQR( 'Left', 'Conjugate Transpose', M, 1, MN, A, LDA,
Line 255 Line 255
          CALL ZAXPY( NR, -CONE, D, 1, C( N-P+1 ), 1 )           CALL ZAXPY( NR, -CONE, D, 1, C( N-P+1 ), 1 )
       END IF        END IF
 *  *
 *     Backward transformation x = Q'*x  *     Backward transformation x = Q**H*x
 *  *
       CALL ZUNMRQ( 'Left', 'Conjugate Transpose', N, 1, P, B, LDB,        CALL ZUNMRQ( 'Left', 'Conjugate Transpose', N, 1, P, B, LDB,
      $             WORK( 1 ), X, N, WORK( P+MN+1 ), LWORK-P-MN, INFO )       $             WORK( 1 ), X, N, WORK( P+MN+1 ), LWORK-P-MN, INFO )

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


CVSweb interface <joel.bertrand@systella.fr>