3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SPFTRS + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spftrs.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spftrs.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spftrs.f">
21 * SUBROUTINE SPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
23 * .. Scalar Arguments ..
24 * CHARACTER TRANSR, UPLO
25 * INTEGER INFO, LDB, N, NRHS
27 * .. Array Arguments ..
28 * REAL A( 0: * ), B( LDB, * )
37 *> SPFTRS solves a system of linear equations A*X = B with a symmetric
38 *> positive definite matrix A using the Cholesky factorization
39 *> A = U**T*U or A = L*L**T computed by SPFTRF.
47 *> TRANSR is CHARACTER*1
48 *> = 'N': The Normal TRANSR of RFP A is stored;
49 *> = 'T': The Transpose TRANSR of RFP A is stored.
54 *> UPLO is CHARACTER*1
55 *> = 'U': Upper triangle of RFP A is stored;
56 *> = 'L': Lower triangle of RFP A is stored.
62 *> The order of the matrix A. N >= 0.
68 *> The number of right hand sides, i.e., the number of columns
69 *> of the matrix B. NRHS >= 0.
74 *> A is REAL array, dimension ( N*(N+1)/2 )
75 *> The triangular factor U or L from the Cholesky factorization
76 *> of RFP A = U**H*U or RFP A = L*L**T, as computed by SPFTRF.
77 *> See note below for more details about RFP A.
82 *> B is REAL array, dimension (LDB,NRHS)
83 *> On entry, the right hand side matrix B.
84 *> On exit, the solution matrix X.
90 *> The leading dimension of the array B. LDB >= max(1,N).
96 *> = 0: successful exit
97 *> < 0: if INFO = -i, the i-th argument had an illegal value
103 *> \author Univ. of Tennessee
104 *> \author Univ. of California Berkeley
105 *> \author Univ. of Colorado Denver
108 *> \date November 2011
110 *> \ingroup realOTHERcomputational
112 *> \par Further Details:
113 * =====================
117 *> We first consider Rectangular Full Packed (RFP) Format when N is
118 *> even. We give an example where N = 6.
120 *> AP is Upper AP is Lower
122 *> 00 01 02 03 04 05 00
123 *> 11 12 13 14 15 10 11
124 *> 22 23 24 25 20 21 22
125 *> 33 34 35 30 31 32 33
126 *> 44 45 40 41 42 43 44
127 *> 55 50 51 52 53 54 55
130 *> Let TRANSR = 'N'. RFP holds AP as follows:
131 *> For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
132 *> three columns of AP upper. The lower triangle A(4:6,0:2) consists of
133 *> the transpose of the first three columns of AP upper.
134 *> For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
135 *> three columns of AP lower. The upper triangle A(0:2,0:2) consists of
136 *> the transpose of the last three columns of AP lower.
137 *> This covers the case N even and TRANSR = 'N'.
149 *> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
150 *> transpose of RFP A above. One therefore gets:
155 *> 03 13 23 33 00 01 02 33 00 10 20 30 40 50
156 *> 04 14 24 34 44 11 12 43 44 11 21 31 41 51
157 *> 05 15 25 35 45 55 22 53 54 55 22 32 42 52
160 *> We then consider Rectangular Full Packed (RFP) Format when N is
161 *> odd. We give an example where N = 5.
163 *> AP is Upper AP is Lower
172 *> Let TRANSR = 'N'. RFP holds AP as follows:
173 *> For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
174 *> three columns of AP upper. The lower triangle A(3:4,0:1) consists of
175 *> the transpose of the first two columns of AP upper.
176 *> For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
177 *> three columns of AP lower. The upper triangle A(0:1,1:2) consists of
178 *> the transpose of the last two columns of AP lower.
179 *> This covers the case N odd and TRANSR = 'N'.
189 *> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
190 *> transpose of RFP A above. One therefore gets:
194 *> 02 12 22 00 01 00 10 20 30 40 50
195 *> 03 13 23 33 11 33 11 21 31 41 51
196 *> 04 14 24 34 44 43 44 22 32 42 52
199 * =====================================================================
200 SUBROUTINE SPFTRS( TRANSR, UPLO, N, NRHS, A, B, LDB, INFO )
202 * -- LAPACK computational routine (version 3.4.0) --
203 * -- LAPACK is a software package provided by Univ. of Tennessee, --
204 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
207 * .. Scalar Arguments ..
208 CHARACTER TRANSR, UPLO
209 INTEGER INFO, LDB, N, NRHS
211 * .. Array Arguments ..
212 REAL A( 0: * ), B( LDB, * )
215 * =====================================================================
219 PARAMETER ( ONE = 1.0E+0 )
221 * .. Local Scalars ..
222 LOGICAL LOWER, NORMALTRANSR
224 * .. External Functions ..
228 * .. External Subroutines ..
229 EXTERNAL XERBLA, STFSM
231 * .. Intrinsic Functions ..
234 * .. Executable Statements ..
236 * Test the input parameters.
239 NORMALTRANSR = LSAME( TRANSR, 'N' )
240 LOWER = LSAME( UPLO, 'L' )
241 IF( .NOT.NORMALTRANSR .AND. .NOT.LSAME( TRANSR, 'T' ) ) THEN
243 ELSE IF( .NOT.LOWER .AND. .NOT.LSAME( UPLO, 'U' ) ) THEN
245 ELSE IF( N.LT.0 ) THEN
247 ELSE IF( NRHS.LT.0 ) THEN
249 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
253 CALL XERBLA( 'SPFTRS', -INFO )
257 * Quick return if possible
259 IF( N.EQ.0 .OR. NRHS.EQ.0 )
262 * start execution: there are two triangular solves
265 CALL STFSM( TRANSR, 'L', UPLO, 'N', 'N', N, NRHS, ONE, A, B,
267 CALL STFSM( TRANSR, 'L', UPLO, 'T', 'N', N, NRHS, ONE, A, B,
270 CALL STFSM( TRANSR, 'L', UPLO, 'T', 'N', N, NRHS, ONE, A, B,
272 CALL STFSM( TRANSR, 'L', UPLO, 'N', 'N', N, NRHS, ONE, A, B,