SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spttrsv.f
Go to the documentation of this file.
1 SUBROUTINE spttrsv( TRANS, N, NRHS, D, E, B, LDB,
2 $ INFO )
3*
4* -- ScaLAPACK auxiliary routine (version 2.0) --
5* Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver
6*
7* Written by Andrew J. Cleary, University of Tennessee.
8* November, 1996.
9* Modified from SPTTRS:
10* -- LAPACK routine (preliminary version) --
11* Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
12* Courant Institute, Argonne National Lab, and Rice University
13*
14* .. Scalar Arguments ..
15 CHARACTER TRANS
16 INTEGER INFO, LDB, N, NRHS
17* ..
18* .. Array Arguments ..
19 REAL D( * )
20 REAL B( LDB, * ), E( * )
21* ..
22*
23* Purpose
24* =======
25*
26* SPTTRSV solves one of the triangular systems
27* L**T* X = B, or L * X = B,
28* where L is the Cholesky factor of a Hermitian positive
29* definite tridiagonal matrix A such that
30* A = L*D*L**H (computed by SPTTRF).
31*
32* Arguments
33* =========
34*
35* TRANS (input) CHARACTER
36* Specifies the form of the system of equations:
37* = 'N': L * X = B (No transpose)
38* = 'T': L**T * X = B (Transpose)
39*
40* N (input) INTEGER
41* The order of the tridiagonal matrix A. N >= 0.
42*
43* NRHS (input) INTEGER
44* The number of right hand sides, i.e., the number of columns
45* of the matrix B. NRHS >= 0.
46*
47* D (input) REAL array, dimension (N)
48* The n diagonal elements of the diagonal matrix D from the
49* factorization computed by SPTTRF.
50*
51* E (input) COMPLEX array, dimension (N-1)
52* The (n-1) off-diagonal elements of the unit bidiagonal
53* factor U or L from the factorization computed by SPTTRF
54* (see UPLO).
55*
56* B (input/output) COMPLEX array, dimension (LDB,NRHS)
57* On entry, the right hand side matrix B.
58* On exit, the solution matrix X.
59*
60* LDB (input) INTEGER
61* The leading dimension of the array B. LDB >= max(1,N).
62*
63* INFO (output) INTEGER
64* = 0: successful exit
65* < 0: if INFO = -i, the i-th argument had an illegal value
66*
67* =====================================================================
68*
69* .. Local Scalars ..
70 LOGICAL NOTRAN
71 INTEGER I, J
72* ..
73* .. External Functions ..
74 LOGICAL LSAME
75 EXTERNAL lsame
76* ..
77* .. External Subroutines ..
78 EXTERNAL xerbla
79* ..
80* .. Intrinsic Functions ..
81 INTRINSIC max
82* ..
83* .. Executable Statements ..
84*
85* Test the input arguments.
86*
87 info = 0
88 notran = lsame( trans, 'N' )
89 IF( .NOT.notran .AND. .NOT.lsame( trans, 'T' ) ) THEN
90 info = -1
91 ELSE IF( n.LT.0 ) THEN
92 info = -2
93 ELSE IF( nrhs.LT.0 ) THEN
94 info = -3
95 ELSE IF( ldb.LT.max( 1, n ) ) THEN
96 info = -7
97 END IF
98 IF( info.NE.0 ) THEN
99 CALL xerbla( 'SPTTRS', -info )
100 RETURN
101 END IF
102*
103* Quick return if possible
104*
105 IF( n.EQ.0 )
106 $ RETURN
107 IF( notran ) THEN
108*
109 DO 60 j = 1, nrhs
110*
111* Solve L * x = b.
112*
113 DO 40 i = 2, n
114 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
115 40 CONTINUE
116 60 CONTINUE
117*
118 ELSE
119*
120 DO 65 j = 1, nrhs
121*
122* Solve L**H * x = b.
123*
124 DO 50 i = n - 1, 1, -1
125 b( i, j ) = b( i, j ) -
126 $ b( i+1, j )*( e( i ) )
127 50 CONTINUE
128 65 CONTINUE
129 ENDIF
130*
131 RETURN
132*
133* End of SPTTRS
134*
135 END
#define max(A, B)
Definition pcgemr.c:180
subroutine spttrsv(trans, n, nrhs, d, e, b, ldb, info)
Definition spttrsv.f:3