122 SUBROUTINE zgetrs( TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
131 INTEGER INFO, LDA, LDB, N, NRHS
135 COMPLEX*16 A( lda, * ), B( ldb, * )
142 parameter ( one = ( 1.0d+0, 0.0d+0 ) )
162 notran = lsame( trans,
'N' )
163 IF( .NOT.notran .AND. .NOT.lsame( trans,
'T' ) .AND. .NOT.
164 $ lsame( trans,
'C' ) )
THEN
166 ELSE IF( n.LT.0 )
THEN
168 ELSE IF( nrhs.LT.0 )
THEN
170 ELSE IF( lda.LT.max( 1, n ) )
THEN
172 ELSE IF( ldb.LT.max( 1, n ) )
THEN
176 CALL xerbla(
'ZGETRS', -info )
182 IF( n.EQ.0 .OR. nrhs.EQ.0 )
191 CALL zlaswp( nrhs, b, ldb, 1, n, ipiv, 1 )
195 CALL ztrsm(
'Left',
'Lower',
'No transpose',
'Unit', n, nrhs,
196 $ one, a, lda, b, ldb )
200 CALL ztrsm(
'Left',
'Upper',
'No transpose',
'Non-unit', n,
201 $ nrhs, one, a, lda, b, ldb )
208 CALL ztrsm(
'Left',
'Upper', trans,
'Non-unit', n, nrhs, one,
213 CALL ztrsm(
'Left',
'Lower', trans,
'Unit', n, nrhs, one, a,
218 CALL zlaswp( nrhs, b, ldb, 1, n, ipiv, -1 )
subroutine zgetrs(TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZGETRS
subroutine zlaswp(N, A, LDA, K1, K2, IPIV, INCX)
ZLASWP performs a series of row interchanges on a general rectangular matrix.
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine ztrsm(SIDE, UPLO, TRANSA, DIAG, M, N, ALPHA, A, LDA, B, LDB)
ZTRSM