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.
190 + .NOT.lsame(trans,
'T') .AND.
191 + .NOT.lsame(trans,
'C'))
THEN
193 ELSE IF (.NOT.lsame(diag,
'U') .AND.
194 + .NOT.lsame(diag,
'N'))
THEN
196 ELSE IF (n.LT.0)
THEN
198 ELSE IF (lda.LT.max(1,n))
THEN
200 ELSE IF (incx.EQ.0)
THEN
204 CALL xerbla(
'CTRSV ',info)
212 noconj = lsame(trans,
'T')
213 nounit = lsame(diag,
'N')
220 ELSE IF (incx.NE.1)
THEN
227 IF (lsame(trans,
'N'))
THEN
231 IF (lsame(uplo,
'U'))
THEN
234 IF (x(j).NE.zero)
THEN
235 IF (nounit) x(j) = x(j)/a(j,j)
238 x(i) = x(i) - temp*a(i,j)
245 IF (x(jx).NE.zero)
THEN
246 IF (nounit) x(jx) = x(jx)/a(j,j)
251 x(ix) = x(ix) - temp*a(i,j)
260 IF (x(j).NE.zero)
THEN
261 IF (nounit) x(j) = x(j)/a(j,j)
264 x(i) = x(i) - temp*a(i,j)
271 IF (x(jx).NE.zero)
THEN
272 IF (nounit) x(jx) = x(jx)/a(j,j)
277 x(ix) = x(ix) - temp*a(i,j)
288 IF (lsame(uplo,
'U'))
THEN
294 temp = temp - a(i,j)*x(i)
296 IF (nounit) temp = temp/a(j,j)
299 temp = temp - conjg(a(i,j))*x(i)
301 IF (nounit) temp = temp/conjg(a(j,j))
312 temp = temp - a(i,j)*x(ix)
315 IF (nounit) temp = temp/a(j,j)
318 temp = temp - conjg(a(i,j))*x(ix)
321 IF (nounit) temp = temp/conjg(a(j,j))
332 DO 150 i = n,j + 1,-1
333 temp = temp - a(i,j)*x(i)
335 IF (nounit) temp = temp/a(j,j)
337 DO 160 i = n,j + 1,-1
338 temp = temp - conjg(a(i,j))*x(i)
340 IF (nounit) temp = temp/conjg(a(j,j))
351 DO 180 i = n,j + 1,-1
352 temp = temp - a(i,j)*x(ix)
355 IF (nounit) temp = temp/a(j,j)
357 DO 190 i = n,j + 1,-1
358 temp = temp - conjg(a(i,j))*x(ix)
361 IF (nounit) temp = temp/conjg(a(j,j))
subroutine xerbla(srname, info)
subroutine ctrsv(uplo, trans, diag, n, a, lda, x, incx)
CTRSV