148 SUBROUTINE ctrsv(UPLO,TRANS,DIAG,N,A,LDA,X,INCX)
156 CHARACTER DIAG,TRANS,UPLO
159 COMPLEX A(LDA,*),X(*)
166 parameter(zero= (0.0e+0,0.0e+0))
170 INTEGER I,INFO,IX,J,JX,KX
171 LOGICAL NOCONJ,NOUNIT
187 IF (.NOT.lsame(uplo,
'U') .AND. .NOT.lsame(uplo,
'L'))
THEN
189 ELSE IF (.NOT.lsame(trans,
'N') .AND. .NOT.lsame(trans,
'T') .AND.
190 + .NOT.lsame(trans,
'C'))
THEN
192 ELSE IF (.NOT.lsame(diag,
'U') .AND. .NOT.lsame(diag,
'N'))
THEN
194 ELSE IF (n.LT.0)
THEN
196 ELSE IF (lda.LT.max(1,n))
THEN
198 ELSE IF (incx.EQ.0)
THEN
202 CALL xerbla(
'CTRSV ',info)
210 noconj = lsame(trans,
'T')
211 nounit = lsame(diag,
'N')
218 ELSE IF (incx.NE.1)
THEN
225 IF (lsame(trans,
'N'))
THEN
229 IF (lsame(uplo,
'U'))
THEN
232 IF (x(j).NE.zero)
THEN
233 IF (nounit) x(j) = x(j)/a(j,j)
236 x(i) = x(i) - temp*a(i,j)
243 IF (x(jx).NE.zero)
THEN
244 IF (nounit) x(jx) = x(jx)/a(j,j)
249 x(ix) = x(ix) - temp*a(i,j)
258 IF (x(j).NE.zero)
THEN
259 IF (nounit) x(j) = x(j)/a(j,j)
262 x(i) = x(i) - temp*a(i,j)
269 IF (x(jx).NE.zero)
THEN
270 IF (nounit) x(jx) = x(jx)/a(j,j)
275 x(ix) = x(ix) - temp*a(i,j)
286 IF (lsame(uplo,
'U'))
THEN
292 temp = temp - a(i,j)*x(i)
294 IF (nounit) temp = temp/a(j,j)
297 temp = temp - conjg(a(i,j))*x(i)
299 IF (nounit) temp = temp/conjg(a(j,j))
310 temp = temp - a(i,j)*x(ix)
313 IF (nounit) temp = temp/a(j,j)
316 temp = temp - conjg(a(i,j))*x(ix)
319 IF (nounit) temp = temp/conjg(a(j,j))
330 DO 150 i = n,j + 1,-1
331 temp = temp - a(i,j)*x(i)
333 IF (nounit) temp = temp/a(j,j)
335 DO 160 i = n,j + 1,-1
336 temp = temp - conjg(a(i,j))*x(i)
338 IF (nounit) temp = temp/conjg(a(j,j))
349 DO 180 i = n,j + 1,-1
350 temp = temp - a(i,j)*x(ix)
353 IF (nounit) temp = temp/a(j,j)
355 DO 190 i = n,j + 1,-1
356 temp = temp - conjg(a(i,j))*x(ix)
359 IF (nounit) temp = temp/conjg(a(j,j))
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine ctrsv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
CTRSV