LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spftrs.f
Go to the documentation of this file.
1*> \brief \b SPFTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SPFTRS + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spftrs.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spftrs.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spftrs.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER TRANSR, UPLO
23* INTEGER INFO, LDB, N, NRHS
24* ..
25* .. Array Arguments ..
26* REAL A( 0: * ), B( LDB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SPFTRS solves a system of linear equations A*X = B with a symmetric
36*> positive definite matrix A using the Cholesky factorization
37*> A = U**T*U or A = L*L**T computed by SPFTRF.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] TRANSR
44*> \verbatim
45*> TRANSR is CHARACTER*1
46*> = 'N': The Normal TRANSR of RFP A is stored;
47*> = 'T': The Transpose TRANSR of RFP A is stored.
48*> \endverbatim
49*>
50*> \param[in] UPLO
51*> \verbatim
52*> UPLO is CHARACTER*1
53*> = 'U': Upper triangle of RFP A is stored;
54*> = 'L': Lower triangle of RFP A is stored.
55*> \endverbatim
56*>
57*> \param[in] N
58*> \verbatim
59*> N is INTEGER
60*> The order of the matrix A. N >= 0.
61*> \endverbatim
62*>
63*> \param[in] NRHS
64*> \verbatim
65*> NRHS is INTEGER
66*> The number of right hand sides, i.e., the number of columns
67*> of the matrix B. NRHS >= 0.
68*> \endverbatim
69*>
70*> \param[in] A
71*> \verbatim
72*> A is REAL array, dimension ( N*(N+1)/2 )
73*> The triangular factor U or L from the Cholesky factorization
74*> of RFP A = U**H*U or RFP A = L*L**T, as computed by SPFTRF.
75*> See note below for more details about RFP A.
76*> \endverbatim
77*>
78*> \param[in,out] B
79*> \verbatim
80*> B is REAL array, dimension (LDB,NRHS)
81*> On entry, the right hand side matrix B.
82*> On exit, the solution matrix X.
83*> \endverbatim
84*>
85*> \param[in] LDB
86*> \verbatim
87*> LDB is INTEGER
88*> The leading dimension of the array B. LDB >= max(1,N).
89*> \endverbatim
90*>
91*> \param[out] INFO
92*> \verbatim
93*> INFO is INTEGER
94*> = 0: successful exit
95*> < 0: if INFO = -i, the i-th argument had an illegal value
96*> \endverbatim
97*
98* Authors:
99* ========
100*
101*> \author Univ. of Tennessee
102*> \author Univ. of California Berkeley
103*> \author Univ. of Colorado Denver
104*> \author NAG Ltd.
105*
106*> \ingroup pftrs
107*
108*> \par Further Details:
109* =====================
110*>
111*> \verbatim
112*>
113*> We first consider Rectangular Full Packed (RFP) Format when N is
114*> even. We give an example where N = 6.
115*>
116*> AP is Upper AP is Lower
117*>
118*> 00 01 02 03 04 05 00
119*> 11 12 13 14 15 10 11
120*> 22 23 24 25 20 21 22
121*> 33 34 35 30 31 32 33
122*> 44 45 40 41 42 43 44
123*> 55 50 51 52 53 54 55
124*>
125*>
126*> Let TRANSR = 'N'. RFP holds AP as follows:
127*> For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
128*> three columns of AP upper. The lower triangle A(4:6,0:2) consists of
129*> the transpose of the first three columns of AP upper.
130*> For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
131*> three columns of AP lower. The upper triangle A(0:2,0:2) consists of
132*> the transpose of the last three columns of AP lower.
133*> This covers the case N even and TRANSR = 'N'.
134*>
135*> RFP A RFP A
136*>
137*> 03 04 05 33 43 53
138*> 13 14 15 00 44 54
139*> 23 24 25 10 11 55
140*> 33 34 35 20 21 22
141*> 00 44 45 30 31 32
142*> 01 11 55 40 41 42
143*> 02 12 22 50 51 52
144*>
145*> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
146*> transpose of RFP A above. One therefore gets:
147*>
148*>
149*> RFP A RFP A
150*>
151*> 03 13 23 33 00 01 02 33 00 10 20 30 40 50
152*> 04 14 24 34 44 11 12 43 44 11 21 31 41 51
153*> 05 15 25 35 45 55 22 53 54 55 22 32 42 52
154*>
155*>
156*> We then consider Rectangular Full Packed (RFP) Format when N is
157*> odd. We give an example where N = 5.
158*>
159*> AP is Upper AP is Lower
160*>
161*> 00 01 02 03 04 00
162*> 11 12 13 14 10 11
163*> 22 23 24 20 21 22
164*> 33 34 30 31 32 33
165*> 44 40 41 42 43 44
166*>
167*>
168*> Let TRANSR = 'N'. RFP holds AP as follows:
169*> For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
170*> three columns of AP upper. The lower triangle A(3:4,0:1) consists of
171*> the transpose of the first two columns of AP upper.
172*> For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
173*> three columns of AP lower. The upper triangle A(0:1,1:2) consists of
174*> the transpose of the last two columns of AP lower.
175*> This covers the case N odd and TRANSR = 'N'.
176*>
177*> RFP A RFP A
178*>
179*> 02 03 04 00 33 43
180*> 12 13 14 10 11 44
181*> 22 23 24 20 21 22
182*> 00 33 34 30 31 32
183*> 01 11 44 40 41 42
184*>
185*> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
186*> transpose of RFP A above. One therefore gets:
187*>
188*> RFP A RFP A
189*>
190*> 02 12 22 00 01 00 10 20 30 40 50
191*> 03 13 23 33 11 33 11 21 31 41 51
192*> 04 14 24 34 44 43 44 22 32 42 52
193*> \endverbatim
194*>
195* =====================================================================
196 SUBROUTINE spftrs( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
197*
198* -- LAPACK computational routine --
199* -- LAPACK is a software package provided by Univ. of Tennessee, --
200* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
201*
202* .. Scalar Arguments ..
203 CHARACTER TRANSR, UPLO
204 INTEGER INFO, LDB, N, NRHS
205* ..
206* .. Array Arguments ..
207 REAL A( 0: * ), B( LDB, * )
208* ..
209*
210* =====================================================================
211*
212* .. Parameters ..
213 REAL ONE
214 parameter( one = 1.0e+0 )
215* ..
216* .. Local Scalars ..
217 LOGICAL LOWER, NORMALTRANSR
218* ..
219* .. External Functions ..
220 LOGICAL LSAME
221 EXTERNAL lsame
222* ..
223* .. External Subroutines ..
224 EXTERNAL xerbla, stfsm
225* ..
226* .. Intrinsic Functions ..
227 INTRINSIC max
228* ..
229* .. Executable Statements ..
230*
231* Test the input parameters.
232*
233 info = 0
234 normaltransr = lsame( transr, 'N' )
235 lower = lsame( uplo, 'L' )
236 IF( .NOT.normaltransr .AND. .NOT.lsame( transr, 'T' ) ) THEN
237 info = -1
238 ELSE IF( .NOT.lower .AND. .NOT.lsame( uplo, 'U' ) ) THEN
239 info = -2
240 ELSE IF( n.LT.0 ) THEN
241 info = -3
242 ELSE IF( nrhs.LT.0 ) THEN
243 info = -4
244 ELSE IF( ldb.LT.max( 1, n ) ) THEN
245 info = -7
246 END IF
247 IF( info.NE.0 ) THEN
248 CALL xerbla( 'SPFTRS', -info )
249 RETURN
250 END IF
251*
252* Quick return if possible
253*
254 IF( n.EQ.0 .OR. nrhs.EQ.0 )
255 $ RETURN
256*
257* start execution: there are two triangular solves
258*
259 IF( lower ) THEN
260 CALL stfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, one, a, b,
261 $ ldb )
262 CALL stfsm( transr, 'L', uplo, 'T', 'N', n, nrhs, one, a, b,
263 $ ldb )
264 ELSE
265 CALL stfsm( transr, 'L', uplo, 'T', 'N', n, nrhs, one, a, b,
266 $ ldb )
267 CALL stfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, one, a, b,
268 $ ldb )
269 END IF
270*
271 RETURN
272*
273* End of SPFTRS
274*
275 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine spftrs(transr, uplo, n, nrhs, a, b, ldb, info)
SPFTRS
Definition spftrs.f:197
subroutine stfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)
STFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition stfsm.f:277