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

◆ cptts2()

subroutine cptts2 ( integer iuplo,
integer n,
integer nrhs,
real, dimension( * ) d,
complex, dimension( * ) e,
complex, dimension( ldb, * ) b,
integer ldb )

CPTTS2 solves a tridiagonal system of the form AX=B using the L D LH factorization computed by spttrf.

Download CPTTS2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> CPTTS2 solves a tridiagonal system of the form
!>    A * X = B
!> using the factorization A = U**H*D*U or A = L*D*L**H computed by CPTTRF.
!> D is a diagonal matrix specified in the vector D, U (or L) is a unit
!> bidiagonal matrix whose superdiagonal (subdiagonal) is specified in
!> the vector E, and X and B are N by NRHS matrices.
!> 
Parameters
[in]IUPLO
!>          IUPLO is INTEGER
!>          Specifies the form of the factorization and whether the
!>          vector E is the superdiagonal of the upper bidiagonal factor
!>          U or the subdiagonal of the lower bidiagonal factor L.
!>          = 1:  A = U**H *D*U, E is the superdiagonal of U
!>          = 0:  A = L*D*L**H, E is the subdiagonal of L
!> 
[in]N
!>          N is INTEGER
!>          The order of the tridiagonal matrix A.  N >= 0.
!> 
[in]NRHS
!>          NRHS is INTEGER
!>          The number of right hand sides, i.e., the number of columns
!>          of the matrix B.  NRHS >= 0.
!> 
[in]D
!>          D is REAL array, dimension (N)
!>          The n diagonal elements of the diagonal matrix D from the
!>          factorization A = U**H *D*U or A = L*D*L**H.
!> 
[in]E
!>          E is COMPLEX array, dimension (N-1)
!>          If IUPLO = 1, the (n-1) superdiagonal elements of the unit
!>          bidiagonal factor U from the factorization A = U**H*D*U.
!>          If IUPLO = 0, the (n-1) subdiagonal elements of the unit
!>          bidiagonal factor L from the factorization A = L*D*L**H.
!> 
[in,out]B
!>          B is COMPLEX array, dimension (LDB,NRHS)
!>          On entry, the right hand side vectors B for the system of
!>          linear equations.
!>          On exit, the solution vectors, X.
!> 
[in]LDB
!>          LDB is INTEGER
!>          The leading dimension of the array B.  LDB >= max(1,N).
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 110 of file cptts2.f.

111*
112* -- LAPACK computational routine --
113* -- LAPACK is a software package provided by Univ. of Tennessee, --
114* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115*
116* .. Scalar Arguments ..
117 INTEGER IUPLO, LDB, N, NRHS
118* ..
119* .. Array Arguments ..
120 REAL D( * )
121 COMPLEX B( LDB, * ), E( * )
122* ..
123*
124* =====================================================================
125*
126* .. Local Scalars ..
127 INTEGER I, J
128* ..
129* .. External Subroutines ..
130 EXTERNAL csscal
131* ..
132* .. Intrinsic Functions ..
133 INTRINSIC conjg
134* ..
135* .. Executable Statements ..
136*
137* Quick return if possible
138*
139 IF( n.LE.1 ) THEN
140 IF( n.EQ.1 )
141 $ CALL csscal( nrhs, 1. / d( 1 ), b, ldb )
142 RETURN
143 END IF
144*
145 IF( iuplo.EQ.1 ) THEN
146*
147* Solve A * X = B using the factorization A = U**H *D*U,
148* overwriting each right hand side vector with its solution.
149*
150 IF( nrhs.LE.2 ) THEN
151 j = 1
152 5 CONTINUE
153*
154* Solve U**H * x = b.
155*
156 DO 10 i = 2, n
157 b( i, j ) = b( i, j ) - b( i-1, j )*conjg( e( i-1 ) )
158 10 CONTINUE
159*
160* Solve D * U * x = b.
161*
162 DO 20 i = 1, n
163 b( i, j ) = b( i, j ) / d( i )
164 20 CONTINUE
165 DO 30 i = n - 1, 1, -1
166 b( i, j ) = b( i, j ) - b( i+1, j )*e( i )
167 30 CONTINUE
168 IF( j.LT.nrhs ) THEN
169 j = j + 1
170 GO TO 5
171 END IF
172 ELSE
173 DO 60 j = 1, nrhs
174*
175* Solve U**H * x = b.
176*
177 DO 40 i = 2, n
178 b( i, j ) = b( i, j ) - b( i-1, j )*conjg( e( i-1 ) )
179 40 CONTINUE
180*
181* Solve D * U * x = b.
182*
183 b( n, j ) = b( n, j ) / d( n )
184 DO 50 i = n - 1, 1, -1
185 b( i, j ) = b( i, j ) / d( i ) - b( i+1, j )*e( i )
186 50 CONTINUE
187 60 CONTINUE
188 END IF
189 ELSE
190*
191* Solve A * X = B using the factorization A = L*D*L**H,
192* overwriting each right hand side vector with its solution.
193*
194 IF( nrhs.LE.2 ) THEN
195 j = 1
196 65 CONTINUE
197*
198* Solve L * x = b.
199*
200 DO 70 i = 2, n
201 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
202 70 CONTINUE
203*
204* Solve D * L**H * x = b.
205*
206 DO 80 i = 1, n
207 b( i, j ) = b( i, j ) / d( i )
208 80 CONTINUE
209 DO 90 i = n - 1, 1, -1
210 b( i, j ) = b( i, j ) - b( i+1, j )*conjg( e( i ) )
211 90 CONTINUE
212 IF( j.LT.nrhs ) THEN
213 j = j + 1
214 GO TO 65
215 END IF
216 ELSE
217 DO 120 j = 1, nrhs
218*
219* Solve L * x = b.
220*
221 DO 100 i = 2, n
222 b( i, j ) = b( i, j ) - b( i-1, j )*e( i-1 )
223 100 CONTINUE
224*
225* Solve D * L**H * x = b.
226*
227 b( n, j ) = b( n, j ) / d( n )
228 DO 110 i = n - 1, 1, -1
229 b( i, j ) = b( i, j ) / d( i ) -
230 $ b( i+1, j )*conjg( e( i ) )
231 110 CONTINUE
232 120 CONTINUE
233 END IF
234 END IF
235*
236 RETURN
237*
238* End of CPTTS2
239*
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78
Here is the call graph for this function:
Here is the caller graph for this function: