LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ dpftrs()

subroutine dpftrs ( character transr,
character uplo,
integer n,
integer nrhs,
double precision, dimension( 0: * ) a,
double precision, dimension( ldb, * ) b,
integer ldb,
integer info )

DPFTRS

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

Purpose:
!> !> DPFTRS solves a system of linear equations A*X = B with a symmetric !> positive definite matrix A using the Cholesky factorization !> A = U**T*U or A = L*L**T computed by DPFTRF. !>
Parameters
[in]TRANSR
!> TRANSR is CHARACTER*1 !> = 'N': The Normal TRANSR of RFP A is stored; !> = 'T': The Transpose TRANSR of RFP A is stored. !>
[in]UPLO
!> UPLO is CHARACTER*1 !> = 'U': Upper triangle of RFP A is stored; !> = 'L': Lower triangle of RFP A is stored. !>
[in]N
!> N is INTEGER !> The order of the 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]A
!> A is DOUBLE PRECISION array, dimension ( N*(N+1)/2 ). !> The triangular factor U or L from the Cholesky factorization !> of RFP A = U**T*U or RFP A = L*L**T, as computed by DPFTRF. !> See note below for more details about RFP A. !>
[in,out]B
!> B is DOUBLE PRECISION array, dimension (LDB,NRHS) !> On entry, the right hand side matrix B. !> On exit, the solution matrix X. !>
[in]LDB
!> LDB is INTEGER !> The leading dimension of the array B. LDB >= max(1,N). !>
[out]INFO
!> INFO is INTEGER !> = 0: successful exit !> < 0: if INFO = -i, the i-th argument had an illegal value !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!> !> We first consider Rectangular Full Packed (RFP) Format when N is !> even. We give an example where N = 6. !> !> AP is Upper AP is Lower !> !> 00 01 02 03 04 05 00 !> 11 12 13 14 15 10 11 !> 22 23 24 25 20 21 22 !> 33 34 35 30 31 32 33 !> 44 45 40 41 42 43 44 !> 55 50 51 52 53 54 55 !> !> !> Let TRANSR = 'N'. RFP holds AP as follows: !> For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last !> three columns of AP upper. The lower triangle A(4:6,0:2) consists of !> the transpose of the first three columns of AP upper. !> For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first !> three columns of AP lower. The upper triangle A(0:2,0:2) consists of !> the transpose of the last three columns of AP lower. !> This covers the case N even and TRANSR = 'N'. !> !> RFP A RFP A !> !> 03 04 05 33 43 53 !> 13 14 15 00 44 54 !> 23 24 25 10 11 55 !> 33 34 35 20 21 22 !> 00 44 45 30 31 32 !> 01 11 55 40 41 42 !> 02 12 22 50 51 52 !> !> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the !> transpose of RFP A above. One therefore gets: !> !> !> RFP A RFP A !> !> 03 13 23 33 00 01 02 33 00 10 20 30 40 50 !> 04 14 24 34 44 11 12 43 44 11 21 31 41 51 !> 05 15 25 35 45 55 22 53 54 55 22 32 42 52 !> !> !> We then consider Rectangular Full Packed (RFP) Format when N is !> odd. We give an example where N = 5. !> !> AP is Upper AP is Lower !> !> 00 01 02 03 04 00 !> 11 12 13 14 10 11 !> 22 23 24 20 21 22 !> 33 34 30 31 32 33 !> 44 40 41 42 43 44 !> !> !> Let TRANSR = 'N'. RFP holds AP as follows: !> For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last !> three columns of AP upper. The lower triangle A(3:4,0:1) consists of !> the transpose of the first two columns of AP upper. !> For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first !> three columns of AP lower. The upper triangle A(0:1,1:2) consists of !> the transpose of the last two columns of AP lower. !> This covers the case N odd and TRANSR = 'N'. !> !> RFP A RFP A !> !> 02 03 04 00 33 43 !> 12 13 14 10 11 44 !> 22 23 24 20 21 22 !> 00 33 34 30 31 32 !> 01 11 44 40 41 42 !> !> Now let TRANSR = 'T'. RFP A in both UPLO cases is just the !> transpose of RFP A above. One therefore gets: !> !> RFP A RFP A !> !> 02 12 22 00 01 00 10 20 30 40 50 !> 03 13 23 33 11 33 11 21 31 41 51 !> 04 14 24 34 44 43 44 22 32 42 52 !>

Definition at line 196 of file dpftrs.f.

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 DOUBLE PRECISION A( 0: * ), B( LDB, * )
208* ..
209*
210* =====================================================================
211*
212* .. Parameters ..
213 DOUBLE PRECISION ONE
214 parameter( one = 1.0d+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, dtfsm
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( 'DPFTRS', -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 dtfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, one, a, b,
261 $ ldb )
262 CALL dtfsm( transr, 'L', uplo, 'T', 'N', n, nrhs, one, a, b,
263 $ ldb )
264 ELSE
265 CALL dtfsm( transr, 'L', uplo, 'T', 'N', n, nrhs, one, a, b,
266 $ ldb )
267 CALL dtfsm( transr, 'L', uplo, 'N', 'N', n, nrhs, one, a, b,
268 $ ldb )
269 END IF
270*
271 RETURN
272*
273* End of DPFTRS
274*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dtfsm(transr, side, uplo, trans, diag, m, n, alpha, a, b, ldb)
DTFSM solves a matrix equation (one operand is a triangular matrix in RFP format).
Definition dtfsm.f:277
Here is the call graph for this function:
Here is the caller graph for this function: