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