LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sgttrs.f
Go to the documentation of this file.
1*> \brief \b SGTTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SGTTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgttrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgttrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgttrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SGTTRS( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B, LDB,
20* INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER TRANS
24* INTEGER INFO, LDB, N, NRHS
25* ..
26* .. Array Arguments ..
27* INTEGER IPIV( * )
28* REAL B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> SGTTRS solves one of the systems of equations
38*> A*X = B or A**T*X = B,
39*> with a tridiagonal matrix A using the LU factorization computed
40*> by SGTTRF.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] TRANS
47*> \verbatim
48*> TRANS is CHARACTER*1
49*> Specifies the form of the system of equations.
50*> = 'N': A * X = B (No transpose)
51*> = 'T': A**T* X = B (Transpose)
52*> = 'C': A**T* X = B (Conjugate transpose = Transpose)
53*> \endverbatim
54*>
55*> \param[in] N
56*> \verbatim
57*> N is INTEGER
58*> The order of the matrix A.
59*> \endverbatim
60*>
61*> \param[in] NRHS
62*> \verbatim
63*> NRHS is INTEGER
64*> The number of right hand sides, i.e., the number of columns
65*> of the matrix B. NRHS >= 0.
66*> \endverbatim
67*>
68*> \param[in] DL
69*> \verbatim
70*> DL is REAL array, dimension (N-1)
71*> The (n-1) multipliers that define the matrix L from the
72*> LU factorization of A.
73*> \endverbatim
74*>
75*> \param[in] D
76*> \verbatim
77*> D is REAL array, dimension (N)
78*> The n diagonal elements of the upper triangular matrix U from
79*> the LU factorization of A.
80*> \endverbatim
81*>
82*> \param[in] DU
83*> \verbatim
84*> DU is REAL array, dimension (N-1)
85*> The (n-1) elements of the first super-diagonal of U.
86*> \endverbatim
87*>
88*> \param[in] DU2
89*> \verbatim
90*> DU2 is REAL array, dimension (N-2)
91*> The (n-2) elements of the second super-diagonal of U.
92*> \endverbatim
93*>
94*> \param[in] IPIV
95*> \verbatim
96*> IPIV is INTEGER array, dimension (N)
97*> The pivot indices; for 1 <= i <= n, row i of the matrix was
98*> interchanged with row IPIV(i). IPIV(i) will always be either
99*> i or i+1; IPIV(i) = i indicates a row interchange was not
100*> required.
101*> \endverbatim
102*>
103*> \param[in,out] B
104*> \verbatim
105*> B is REAL array, dimension (LDB,NRHS)
106*> On entry, the matrix of right hand side vectors B.
107*> On exit, B is overwritten by the solution vectors X.
108*> \endverbatim
109*>
110*> \param[in] LDB
111*> \verbatim
112*> LDB is INTEGER
113*> The leading dimension of the array B. LDB >= max(1,N).
114*> \endverbatim
115*>
116*> \param[out] INFO
117*> \verbatim
118*> INFO is INTEGER
119*> = 0: successful exit
120*> < 0: if INFO = -i, the i-th argument had an illegal value
121*> \endverbatim
122*
123* Authors:
124* ========
125*
126*> \author Univ. of Tennessee
127*> \author Univ. of California Berkeley
128*> \author Univ. of Colorado Denver
129*> \author NAG Ltd.
130*
131*> \ingroup gttrs
132*
133* =====================================================================
134 SUBROUTINE sgttrs( TRANS, N, NRHS, DL, D, DU, DU2, IPIV, B,
135 $ LDB,
136 $ INFO )
137*
138* -- LAPACK computational routine --
139* -- LAPACK is a software package provided by Univ. of Tennessee, --
140* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
141*
142* .. Scalar Arguments ..
143 CHARACTER TRANS
144 INTEGER INFO, LDB, N, NRHS
145* ..
146* .. Array Arguments ..
147 INTEGER IPIV( * )
148 REAL B( LDB, * ), D( * ), DL( * ), DU( * ), DU2( * )
149* ..
150*
151* =====================================================================
152*
153* .. Local Scalars ..
154 LOGICAL NOTRAN
155 INTEGER ITRANS, J, JB, NB
156* ..
157* .. External Functions ..
158 INTEGER ILAENV
159 EXTERNAL ILAENV
160* ..
161* .. External Subroutines ..
162 EXTERNAL sgtts2, xerbla
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC max, min
166* ..
167* .. Executable Statements ..
168*
169 info = 0
170 notran = ( trans.EQ.'N' .OR. trans.EQ.'n' )
171 IF( .NOT.notran .AND. .NOT.( trans.EQ.'T' .OR. trans.EQ.
172 $ 't' ) .AND. .NOT.( trans.EQ.'C' .OR. trans.EQ.'c' ) ) THEN
173 info = -1
174 ELSE IF( n.LT.0 ) THEN
175 info = -2
176 ELSE IF( nrhs.LT.0 ) THEN
177 info = -3
178 ELSE IF( ldb.LT.max( n, 1 ) ) THEN
179 info = -10
180 END IF
181 IF( info.NE.0 ) THEN
182 CALL xerbla( 'SGTTRS', -info )
183 RETURN
184 END IF
185*
186* Quick return if possible
187*
188 IF( n.EQ.0 .OR. nrhs.EQ.0 )
189 $ RETURN
190*
191* Decode TRANS
192*
193 IF( notran ) THEN
194 itrans = 0
195 ELSE
196 itrans = 1
197 END IF
198*
199* Determine the number of right-hand sides to solve at a time.
200*
201 IF( nrhs.EQ.1 ) THEN
202 nb = 1
203 ELSE
204 nb = max( 1, ilaenv( 1, 'SGTTRS', trans, n, nrhs, -1, -1 ) )
205 END IF
206*
207 IF( nb.GE.nrhs ) THEN
208 CALL sgtts2( itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb )
209 ELSE
210 DO 10 j = 1, nrhs, nb
211 jb = min( nrhs-j+1, nb )
212 CALL sgtts2( itrans, n, jb, dl, d, du, du2, ipiv, b( 1,
213 $ j ),
214 $ ldb )
215 10 CONTINUE
216 END IF
217*
218* End of SGTTRS
219*
220 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgttrs(trans, n, nrhs, dl, d, du, du2, ipiv, b, ldb, info)
SGTTRS
Definition sgttrs.f:137
subroutine sgtts2(itrans, n, nrhs, dl, d, du, du2, ipiv, b, ldb)
SGTTS2 solves a system of linear equations with a tridiagonal matrix using the LU factorization compu...
Definition sgtts2.f:127