SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cpttrsv.f
Go to the documentation of this file.
1 SUBROUTINE cpttrsv( UPLO, 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 CPTTRS:
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 UPLO, TRANS
16 INTEGER INFO, LDB, N, NRHS
17* ..
18* .. Array Arguments ..
19 REAL D( * )
20 COMPLEX B( LDB, * ), E( * )
21* ..
22*
23* Purpose
24* =======
25*
26* CPTTRSV solves one of the triangular systems
27* L * X = B, or L**H * X = B,
28* U * X = B, or U**H * X = B,
29* where L or U is the Cholesky factor of a Hermitian positive
30* definite tridiagonal matrix A such that
31* A = U**H*D*U or A = L*D*L**H (computed by CPTTRF).
32*
33* Arguments
34* =========
35*
36* UPLO (input) CHARACTER*1
37* Specifies whether the superdiagonal or the subdiagonal
38* of the tridiagonal matrix A is stored and the form of the
39* factorization:
40* = 'U': E is the superdiagonal of U, and A = U'*D*U;
41* = 'L': E is the subdiagonal of L, and A = L*D*L'.
42* (The two forms are equivalent if A is real.)
43*
44* TRANS (input) CHARACTER
45* Specifies the form of the system of equations:
46* = 'N': L * X = B (No transpose)
47* = 'N': L * X = B (No transpose)
48* = 'C': U**H * X = B (Conjugate transpose)
49* = 'C': L**H * X = B (Conjugate transpose)
50*
51* N (input) INTEGER
52* The order of the tridiagonal matrix A. N >= 0.
53*
54* NRHS (input) INTEGER
55* The number of right hand sides, i.e., the number of columns
56* of the matrix B. NRHS >= 0.
57*
58* D (input) REAL array, dimension (N)
59* The n diagonal elements of the diagonal matrix D from the
60* factorization computed by CPTTRF.
61*
62* E (input) COMPLEX array, dimension (N-1)
63* The (n-1) off-diagonal elements of the unit bidiagonal
64* factor U or L from the factorization computed by CPTTRF
65* (see UPLO).
66*
67* B (input/output) COMPLEX array, dimension (LDB,NRHS)
68* On entry, the right hand side matrix B.
69* On exit, the solution matrix X.
70*
71* LDB (input) INTEGER
72* The leading dimension of the array B. LDB >= max(1,N).
73*
74* INFO (output) INTEGER
75* = 0: successful exit
76* < 0: if INFO = -i, the i-th argument had an illegal value
77*
78* =====================================================================
79*
80* .. Local Scalars ..
81 LOGICAL NOTRAN, UPPER
82 INTEGER I, J
83* ..
84* .. External Functions ..
85 LOGICAL LSAME
86 EXTERNAL lsame
87* ..
88* .. External Subroutines ..
89 EXTERNAL xerbla
90* ..
91* .. Intrinsic Functions ..
92 INTRINSIC conjg, max
93* ..
94* .. Executable Statements ..
95*
96* Test the input arguments.
97*
98 info = 0
99 notran = lsame( trans, 'N' )
100 upper = lsame( uplo, 'U' )
101 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
102 info = -1
103 ELSE IF( .NOT.notran .AND. .NOT.
104 $ lsame( trans, 'C' ) ) THEN
105 info = -2
106 ELSE IF( n.LT.0 ) THEN
107 info = -3
108 ELSE IF( nrhs.LT.0 ) THEN
109 info = -4
110 ELSE IF( ldb.LT.max( 1, n ) ) THEN
111 info = -8
112 END IF
113 IF( info.NE.0 ) THEN
114 CALL xerbla( 'CPTTRS', -info )
115 RETURN
116 END IF
117*
118* Quick return if possible
119*
120 IF( n.EQ.0 )
121 $ RETURN
122*
123 IF( upper ) THEN
124*
125 IF( .NOT.notran ) THEN
126*
127 DO 30 j = 1, nrhs
128*
129* Solve U**T (or H) * x = b.
130*
131 DO 10 i = 2, n
132 b( i, j ) = b( i, j ) - b( i-1, j )*conjg( e( i-1 ) )
133 10 CONTINUE
134 30 CONTINUE
135*
136 ELSE
137*
138 DO 35 j = 1, nrhs
139*
140* Solve U * x = b.
141*
142 DO 20 i = n - 1, 1, -1
143 b( i, j ) = b( i, j ) - b( i+1, j )*e( i )
144 20 CONTINUE
145 35 CONTINUE
146 ENDIF
147*
148 ELSE
149*
150 IF( notran ) THEN
151*
152 DO 60 j = 1, nrhs
153*
154* Solve L * x = b.
155*
156 DO 40 i = 2, n
157 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
158 40 CONTINUE
159 60 CONTINUE
160*
161 ELSE
162*
163 DO 65 j = 1, nrhs
164*
165* Solve L**H * x = b.
166*
167 DO 50 i = n - 1, 1, -1
168 b( i, j ) = b( i, j ) -
169 $ b( i+1, j )*conjg( e( i ) )
170 50 CONTINUE
171 65 CONTINUE
172 ENDIF
173*
174 END IF
175*
176 RETURN
177*
178* End of CPTTRS
179*
180 END
subroutine cpttrsv(uplo, trans, n, nrhs, d, e, b, ldb, info)
Definition cpttrsv.f:3
#define max(A, B)
Definition pcgemr.c:180