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

version 1.7, 2010/12/21 13:53:41 version 1.8, 2011/07/22 07:38:13
Line 1 Line 1
       SUBROUTINE DTRSYL( TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C,        SUBROUTINE DTRSYL( TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C,
      $                   LDC, SCALE, INFO )       $                   LDC, SCALE, INFO )
 *  *
 *  -- LAPACK routine (version 3.2) --  *  -- LAPACK 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..--
 *     November 2006  *  -- April 2011                                                      --
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       CHARACTER          TRANA, TRANB        CHARACTER          TRANA, TRANB
Line 355 Line 355
 *  *
       ELSE IF( .NOT.NOTRNA .AND. NOTRNB ) THEN        ELSE IF( .NOT.NOTRNA .AND. NOTRNB ) THEN
 *  *
 *        Solve    A' *X + ISGN*X*B = scale*C.  *        Solve    A**T *X + ISGN*X*B = scale*C.
 *  *
 *        The (K,L)th block of X is determined starting from  *        The (K,L)th block of X is determined starting from
 *        upper-left corner column by column by  *        upper-left corner column by column by
 *  *
 *          A(K,K)'*X(K,L) + ISGN*X(K,L)*B(L,L) = C(K,L) - R(K,L)  *          A(K,K)**T*X(K,L) + ISGN*X(K,L)*B(L,L) = C(K,L) - R(K,L)
 *  *
 *        Where  *        Where
 *                   K-1                        L-1  *                   K-1                          L-1
 *          R(K,L) = SUM [A(I,K)'*X(I,L)] +ISGN*SUM [X(K,J)*B(J,L)]  *          R(K,L) = SUM [A(I,K)**T*X(I,L)] +ISGN*SUM [X(K,J)*B(J,L)]
 *                   I=1                        J=1  *                   I=1                          J=1
 *  *
 *        Start column loop (index = L)  *        Start column loop (index = L)
 *        L1 (L2): column index of the first (last) row of X(K,L)  *        L1 (L2): column index of the first (last) row of X(K,L)
Line 530 Line 530
 *  *
       ELSE IF( .NOT.NOTRNA .AND. .NOT.NOTRNB ) THEN        ELSE IF( .NOT.NOTRNA .AND. .NOT.NOTRNB ) THEN
 *  *
 *        Solve    A'*X + ISGN*X*B' = scale*C.  *        Solve    A**T*X + ISGN*X*B**T = scale*C.
 *  *
 *        The (K,L)th block of X is determined starting from  *        The (K,L)th block of X is determined starting from
 *        top-right corner column by column by  *        top-right corner column by column by
 *  *
 *           A(K,K)'*X(K,L) + ISGN*X(K,L)*B(L,L)' = C(K,L) - R(K,L)  *           A(K,K)**T*X(K,L) + ISGN*X(K,L)*B(L,L)**T = C(K,L) - R(K,L)
 *  *
 *        Where  *        Where
 *                     K-1                          N  *                     K-1                            N
 *            R(K,L) = SUM [A(I,K)'*X(I,L)] + ISGN*SUM [X(K,J)*B(L,J)'].  *            R(K,L) = SUM [A(I,K)**T*X(I,L)] + ISGN*SUM [X(K,J)*B(L,J)**T].
 *                     I=1                        J=L+1  *                     I=1                          J=L+1
 *  *
 *        Start column loop (index = L)  *        Start column loop (index = L)
 *        L1 (L2): column index of the first (last) row of X(K,L)  *        L1 (L2): column index of the first (last) row of X(K,L)
Line 714 Line 714
 *  *
       ELSE IF( NOTRNA .AND. .NOT.NOTRNB ) THEN        ELSE IF( NOTRNA .AND. .NOT.NOTRNB ) THEN
 *  *
 *        Solve    A*X + ISGN*X*B' = scale*C.  *        Solve    A*X + ISGN*X*B**T = scale*C.
 *  *
 *        The (K,L)th block of X is determined starting from  *        The (K,L)th block of X is determined starting from
 *        bottom-right corner column by column by  *        bottom-right corner column by column by
 *  *
 *            A(K,K)*X(K,L) + ISGN*X(K,L)*B(L,L)' = C(K,L) - R(K,L)  *            A(K,K)*X(K,L) + ISGN*X(K,L)*B(L,L)**T = C(K,L) - R(K,L)
 *  *
 *        Where  *        Where
 *                      M                          N  *                      M                          N
 *            R(K,L) = SUM [A(K,I)*X(I,L)] + ISGN*SUM [X(K,J)*B(L,J)'].  *            R(K,L) = SUM [A(K,I)*X(I,L)] + ISGN*SUM [X(K,J)*B(L,J)**T].
 *                    I=K+1                      J=L+1  *                    I=K+1                      J=L+1
 *  *
 *        Start column loop (index = L)  *        Start column loop (index = L)

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


CVSweb interface <joel.bertrand@systella.fr>