LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dpotrs.f
Go to the documentation of this file.
1*> \brief \b DPOTRS
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DPOTRS + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpotrs.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpotrs.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpotrs.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DPOTRS( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INFO, LDA, LDB, N, NRHS
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION A( LDA, * ), B( LDB, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> DPOTRS 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 DPOTRF.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] UPLO
46*> \verbatim
47*> UPLO is CHARACTER*1
48*> = 'U': Upper triangle of A is stored;
49*> = 'L': Lower triangle of A is stored.
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The order of the matrix A. N >= 0.
56*> \endverbatim
57*>
58*> \param[in] NRHS
59*> \verbatim
60*> NRHS is INTEGER
61*> The number of right hand sides, i.e., the number of columns
62*> of the matrix B. NRHS >= 0.
63*> \endverbatim
64*>
65*> \param[in] A
66*> \verbatim
67*> A is DOUBLE PRECISION array, dimension (LDA,N)
68*> The triangular factor U or L from the Cholesky factorization
69*> A = U**T*U or A = L*L**T, as computed by DPOTRF.
70*> \endverbatim
71*>
72*> \param[in] LDA
73*> \verbatim
74*> LDA is INTEGER
75*> The leading dimension of the array A. LDA >= max(1,N).
76*> \endverbatim
77*>
78*> \param[in,out] B
79*> \verbatim
80*> B is DOUBLE PRECISION 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 potrs
107*
108* =====================================================================
109 SUBROUTINE dpotrs( UPLO, N, NRHS, A, LDA, B, LDB, INFO )
110*
111* -- LAPACK computational routine --
112* -- LAPACK is a software package provided by Univ. of Tennessee, --
113* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114*
115* .. Scalar Arguments ..
116 CHARACTER UPLO
117 INTEGER INFO, LDA, LDB, N, NRHS
118* ..
119* .. Array Arguments ..
120 DOUBLE PRECISION A( LDA, * ), B( LDB, * )
121* ..
122*
123* =====================================================================
124*
125* .. Parameters ..
126 DOUBLE PRECISION ONE
127 parameter( one = 1.0d+0 )
128* ..
129* .. Local Scalars ..
130 LOGICAL UPPER
131* ..
132* .. External Functions ..
133 LOGICAL LSAME
134 EXTERNAL lsame
135* ..
136* .. External Subroutines ..
137 EXTERNAL dtrsm, xerbla
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC max
141* ..
142* .. Executable Statements ..
143*
144* Test the input parameters.
145*
146 info = 0
147 upper = lsame( uplo, 'U' )
148 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
149 info = -1
150 ELSE IF( n.LT.0 ) THEN
151 info = -2
152 ELSE IF( nrhs.LT.0 ) THEN
153 info = -3
154 ELSE IF( lda.LT.max( 1, n ) ) THEN
155 info = -5
156 ELSE IF( ldb.LT.max( 1, n ) ) THEN
157 info = -7
158 END IF
159 IF( info.NE.0 ) THEN
160 CALL xerbla( 'DPOTRS', -info )
161 RETURN
162 END IF
163*
164* Quick return if possible
165*
166 IF( n.EQ.0 .OR. nrhs.EQ.0 )
167 $ RETURN
168*
169 IF( upper ) THEN
170*
171* Solve A*X = B where A = U**T *U.
172*
173* Solve U**T *X = B, overwriting B with X.
174*
175 CALL dtrsm( 'Left', 'Upper', 'Transpose', 'Non-unit', n, nrhs,
176 $ one, a, lda, b, ldb )
177*
178* Solve U*X = B, overwriting B with X.
179*
180 CALL dtrsm( 'Left', 'Upper', 'No transpose', 'Non-unit', n,
181 $ nrhs, one, a, lda, b, ldb )
182 ELSE
183*
184* Solve A*X = B where A = L*L**T.
185*
186* Solve L*X = B, overwriting B with X.
187*
188 CALL dtrsm( 'Left', 'Lower', 'No transpose', 'Non-unit', n,
189 $ nrhs, one, a, lda, b, ldb )
190*
191* Solve L**T *X = B, overwriting B with X.
192*
193 CALL dtrsm( 'Left', 'Lower', 'Transpose', 'Non-unit', n, nrhs,
194 $ one, a, lda, b, ldb )
195 END IF
196*
197 RETURN
198*
199* End of DPOTRS
200*
201 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
DPOTRS
Definition dpotrs.f:110
subroutine dtrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
DTRSM
Definition dtrsm.f:181