LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dtrsv()

subroutine dtrsv ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
double precision, dimension(lda,*)  A,
integer  LDA,
double precision, dimension(*)  X,
integer  INCX 
)

DTRSV

Purpose:
 DTRSV  solves one of the systems of equations

    A*x = b,   or   A**T*x = b,

 where b and x are n element vectors and A is an n by n unit, or
 non-unit, upper or lower triangular matrix.

 No test for singularity or near-singularity is included in this
 routine. Such tests must be performed before calling this routine.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the matrix is an upper or
           lower triangular matrix as follows:

              UPLO = 'U' or 'u'   A is an upper triangular matrix.

              UPLO = 'L' or 'l'   A is a lower triangular matrix.
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the equations to be solved as
           follows:

              TRANS = 'N' or 'n'   A*x = b.

              TRANS = 'T' or 't'   A**T*x = b.

              TRANS = 'C' or 'c'   A**T*x = b.
[in]DIAG
          DIAG is CHARACTER*1
           On entry, DIAG specifies whether or not A is unit
           triangular as follows:

              DIAG = 'U' or 'u'   A is assumed to be unit triangular.

              DIAG = 'N' or 'n'   A is not assumed to be unit
                                  triangular.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]A
          A is DOUBLE PRECISION array, dimension ( LDA, N )
           Before entry with  UPLO = 'U' or 'u', the leading n by n
           upper triangular part of the array A must contain the upper
           triangular matrix and the strictly lower triangular part of
           A is not referenced.
           Before entry with UPLO = 'L' or 'l', the leading n by n
           lower triangular part of the array A must contain the lower
           triangular matrix and the strictly upper triangular part of
           A is not referenced.
           Note that when  DIAG = 'U' or 'u', the diagonal elements of
           A are not referenced either, but are assumed to be unity.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, n ).
[in,out]X
          X is DOUBLE PRECISION array, dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element right-hand side vector b. On exit, X is overwritten
           with the solution vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.

  Level 2 Blas routine.

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 142 of file dtrsv.f.

143*
144* -- Reference BLAS level1 routine --
145* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
146* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
147*
148* .. Scalar Arguments ..
149 INTEGER INCX,LDA,N
150 CHARACTER DIAG,TRANS,UPLO
151* ..
152* .. Array Arguments ..
153 DOUBLE PRECISION A(LDA,*),X(*)
154* ..
155*
156* =====================================================================
157*
158* .. Parameters ..
159 DOUBLE PRECISION ZERO
160 parameter(zero=0.0d+0)
161* ..
162* .. Local Scalars ..
163 DOUBLE PRECISION TEMP
164 INTEGER I,INFO,IX,J,JX,KX
165 LOGICAL NOUNIT
166* ..
167* .. External Functions ..
168 LOGICAL LSAME
169 EXTERNAL lsame
170* ..
171* .. External Subroutines ..
172 EXTERNAL xerbla
173* ..
174* .. Intrinsic Functions ..
175 INTRINSIC max
176* ..
177*
178* Test the input parameters.
179*
180 info = 0
181 IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
182 info = 1
183 ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
184 + .NOT.lsame(trans,'C')) THEN
185 info = 2
186 ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
187 info = 3
188 ELSE IF (n.LT.0) THEN
189 info = 4
190 ELSE IF (lda.LT.max(1,n)) THEN
191 info = 6
192 ELSE IF (incx.EQ.0) THEN
193 info = 8
194 END IF
195 IF (info.NE.0) THEN
196 CALL xerbla('DTRSV ',info)
197 RETURN
198 END IF
199*
200* Quick return if possible.
201*
202 IF (n.EQ.0) RETURN
203*
204 nounit = lsame(diag,'N')
205*
206* Set up the start point in X if the increment is not unity. This
207* will be ( N - 1 )*INCX too small for descending loops.
208*
209 IF (incx.LE.0) THEN
210 kx = 1 - (n-1)*incx
211 ELSE IF (incx.NE.1) THEN
212 kx = 1
213 END IF
214*
215* Start the operations. In this version the elements of A are
216* accessed sequentially with one pass through A.
217*
218 IF (lsame(trans,'N')) THEN
219*
220* Form x := inv( A )*x.
221*
222 IF (lsame(uplo,'U')) THEN
223 IF (incx.EQ.1) THEN
224 DO 20 j = n,1,-1
225 IF (x(j).NE.zero) THEN
226 IF (nounit) x(j) = x(j)/a(j,j)
227 temp = x(j)
228 DO 10 i = j - 1,1,-1
229 x(i) = x(i) - temp*a(i,j)
230 10 CONTINUE
231 END IF
232 20 CONTINUE
233 ELSE
234 jx = kx + (n-1)*incx
235 DO 40 j = n,1,-1
236 IF (x(jx).NE.zero) THEN
237 IF (nounit) x(jx) = x(jx)/a(j,j)
238 temp = x(jx)
239 ix = jx
240 DO 30 i = j - 1,1,-1
241 ix = ix - incx
242 x(ix) = x(ix) - temp*a(i,j)
243 30 CONTINUE
244 END IF
245 jx = jx - incx
246 40 CONTINUE
247 END IF
248 ELSE
249 IF (incx.EQ.1) THEN
250 DO 60 j = 1,n
251 IF (x(j).NE.zero) THEN
252 IF (nounit) x(j) = x(j)/a(j,j)
253 temp = x(j)
254 DO 50 i = j + 1,n
255 x(i) = x(i) - temp*a(i,j)
256 50 CONTINUE
257 END IF
258 60 CONTINUE
259 ELSE
260 jx = kx
261 DO 80 j = 1,n
262 IF (x(jx).NE.zero) THEN
263 IF (nounit) x(jx) = x(jx)/a(j,j)
264 temp = x(jx)
265 ix = jx
266 DO 70 i = j + 1,n
267 ix = ix + incx
268 x(ix) = x(ix) - temp*a(i,j)
269 70 CONTINUE
270 END IF
271 jx = jx + incx
272 80 CONTINUE
273 END IF
274 END IF
275 ELSE
276*
277* Form x := inv( A**T )*x.
278*
279 IF (lsame(uplo,'U')) THEN
280 IF (incx.EQ.1) THEN
281 DO 100 j = 1,n
282 temp = x(j)
283 DO 90 i = 1,j - 1
284 temp = temp - a(i,j)*x(i)
285 90 CONTINUE
286 IF (nounit) temp = temp/a(j,j)
287 x(j) = temp
288 100 CONTINUE
289 ELSE
290 jx = kx
291 DO 120 j = 1,n
292 temp = x(jx)
293 ix = kx
294 DO 110 i = 1,j - 1
295 temp = temp - a(i,j)*x(ix)
296 ix = ix + incx
297 110 CONTINUE
298 IF (nounit) temp = temp/a(j,j)
299 x(jx) = temp
300 jx = jx + incx
301 120 CONTINUE
302 END IF
303 ELSE
304 IF (incx.EQ.1) THEN
305 DO 140 j = n,1,-1
306 temp = x(j)
307 DO 130 i = n,j + 1,-1
308 temp = temp - a(i,j)*x(i)
309 130 CONTINUE
310 IF (nounit) temp = temp/a(j,j)
311 x(j) = temp
312 140 CONTINUE
313 ELSE
314 kx = kx + (n-1)*incx
315 jx = kx
316 DO 160 j = n,1,-1
317 temp = x(jx)
318 ix = kx
319 DO 150 i = n,j + 1,-1
320 temp = temp - a(i,j)*x(ix)
321 ix = ix - incx
322 150 CONTINUE
323 IF (nounit) temp = temp/a(j,j)
324 x(jx) = temp
325 jx = jx - incx
326 160 CONTINUE
327 END IF
328 END IF
329 END IF
330*
331 RETURN
332*
333* End of DTRSV
334*
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
Here is the call graph for this function:
Here is the caller graph for this function: