Annotation of rpl/lapack/lapack/zhesv.f, revision 1.19
1.10 bertrand 1: *> \brief <b> ZHESV computes the solution to system of linear equations A * X = B for HE matrices</b>
2: *
3: * =========== DOCUMENTATION ===========
4: *
1.16 bertrand 5: * Online html documentation available at
6: * http://www.netlib.org/lapack/explore-html/
1.10 bertrand 7: *
8: *> \htmlonly
1.16 bertrand 9: *> Download ZHESV + dependencies
10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhesv.f">
11: *> [TGZ]</a>
12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhesv.f">
13: *> [ZIP]</a>
14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhesv.f">
1.10 bertrand 15: *> [TXT]</a>
1.16 bertrand 16: *> \endhtmlonly
1.10 bertrand 17: *
18: * Definition:
19: * ===========
20: *
21: * SUBROUTINE ZHESV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
22: * LWORK, INFO )
1.16 bertrand 23: *
1.10 bertrand 24: * .. Scalar Arguments ..
25: * CHARACTER UPLO
26: * INTEGER INFO, LDA, LDB, LWORK, N, NRHS
27: * ..
28: * .. Array Arguments ..
29: * INTEGER IPIV( * )
30: * COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
31: * ..
1.16 bertrand 32: *
1.10 bertrand 33: *
34: *> \par Purpose:
35: * =============
36: *>
37: *> \verbatim
38: *>
39: *> ZHESV computes the solution to a complex system of linear equations
40: *> A * X = B,
41: *> where A is an N-by-N Hermitian matrix and X and B are N-by-NRHS
42: *> matrices.
43: *>
44: *> The diagonal pivoting method is used to factor A as
45: *> A = U * D * U**H, if UPLO = 'U', or
46: *> A = L * D * L**H, if UPLO = 'L',
47: *> where U (or L) is a product of permutation and unit upper (lower)
48: *> triangular matrices, and D is Hermitian and block diagonal with
49: *> 1-by-1 and 2-by-2 diagonal blocks. The factored form of A is then
50: *> used to solve the system of equations A * X = B.
51: *> \endverbatim
52: *
53: * Arguments:
54: * ==========
55: *
56: *> \param[in] UPLO
57: *> \verbatim
58: *> UPLO is CHARACTER*1
59: *> = 'U': Upper triangle of A is stored;
60: *> = 'L': Lower triangle of A is stored.
61: *> \endverbatim
62: *>
63: *> \param[in] N
64: *> \verbatim
65: *> N is INTEGER
66: *> The number of linear equations, i.e., the order of the
67: *> matrix A. N >= 0.
68: *> \endverbatim
69: *>
70: *> \param[in] NRHS
71: *> \verbatim
72: *> NRHS is INTEGER
73: *> The number of right hand sides, i.e., the number of columns
74: *> of the matrix B. NRHS >= 0.
75: *> \endverbatim
76: *>
77: *> \param[in,out] A
78: *> \verbatim
79: *> A is COMPLEX*16 array, dimension (LDA,N)
80: *> On entry, the Hermitian matrix A. If UPLO = 'U', the leading
81: *> N-by-N upper triangular part of A contains the upper
82: *> triangular part of the matrix A, and the strictly lower
83: *> triangular part of A is not referenced. If UPLO = 'L', the
84: *> leading N-by-N lower triangular part of A contains the lower
85: *> triangular part of the matrix A, and the strictly upper
86: *> triangular part of A is not referenced.
87: *>
88: *> On exit, if INFO = 0, the block diagonal matrix D and the
89: *> multipliers used to obtain the factor U or L from the
90: *> factorization A = U*D*U**H or A = L*D*L**H as computed by
91: *> ZHETRF.
92: *> \endverbatim
93: *>
94: *> \param[in] LDA
95: *> \verbatim
96: *> LDA is INTEGER
97: *> The leading dimension of the array A. LDA >= max(1,N).
98: *> \endverbatim
99: *>
100: *> \param[out] IPIV
101: *> \verbatim
102: *> IPIV is INTEGER array, dimension (N)
103: *> Details of the interchanges and the block structure of D, as
104: *> determined by ZHETRF. If IPIV(k) > 0, then rows and columns
105: *> k and IPIV(k) were interchanged, and D(k,k) is a 1-by-1
106: *> diagonal block. If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0,
107: *> then rows and columns k-1 and -IPIV(k) were interchanged and
108: *> D(k-1:k,k-1:k) is a 2-by-2 diagonal block. If UPLO = 'L' and
109: *> IPIV(k) = IPIV(k+1) < 0, then rows and columns k+1 and
110: *> -IPIV(k) were interchanged and D(k:k+1,k:k+1) is a 2-by-2
111: *> diagonal block.
112: *> \endverbatim
113: *>
114: *> \param[in,out] B
115: *> \verbatim
116: *> B is COMPLEX*16 array, dimension (LDB,NRHS)
117: *> On entry, the N-by-NRHS right hand side matrix B.
118: *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
119: *> \endverbatim
120: *>
121: *> \param[in] LDB
122: *> \verbatim
123: *> LDB is INTEGER
124: *> The leading dimension of the array B. LDB >= max(1,N).
125: *> \endverbatim
126: *>
127: *> \param[out] WORK
128: *> \verbatim
129: *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
130: *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
131: *> \endverbatim
132: *>
133: *> \param[in] LWORK
134: *> \verbatim
135: *> LWORK is INTEGER
136: *> The length of WORK. LWORK >= 1, and for best performance
137: *> LWORK >= max(1,N*NB), where NB is the optimal blocksize for
138: *> ZHETRF.
139: *> for LWORK < N, TRS will be done with Level BLAS 2
140: *> for LWORK >= N, TRS will be done with Level BLAS 3
141: *>
142: *> If LWORK = -1, then a workspace query is assumed; the routine
143: *> only calculates the optimal size of the WORK array, returns
144: *> this value as the first entry of the WORK array, and no error
145: *> message related to LWORK is issued by XERBLA.
146: *> \endverbatim
147: *>
148: *> \param[out] INFO
149: *> \verbatim
150: *> INFO is INTEGER
151: *> = 0: successful exit
152: *> < 0: if INFO = -i, the i-th argument had an illegal value
153: *> > 0: if INFO = i, D(i,i) is exactly zero. The factorization
154: *> has been completed, but the block diagonal matrix D is
155: *> exactly singular, so the solution could not be computed.
156: *> \endverbatim
157: *
158: * Authors:
159: * ========
160: *
1.16 bertrand 161: *> \author Univ. of Tennessee
162: *> \author Univ. of California Berkeley
163: *> \author Univ. of Colorado Denver
164: *> \author NAG Ltd.
1.10 bertrand 165: *
166: *> \ingroup complex16HEsolve
167: *
168: * =====================================================================
1.1 bertrand 169: SUBROUTINE ZHESV( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
170: $ LWORK, INFO )
171: *
1.19 ! bertrand 172: * -- LAPACK driver routine --
1.1 bertrand 173: * -- LAPACK is a software package provided by Univ. of Tennessee, --
174: * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
175: *
176: * .. Scalar Arguments ..
177: CHARACTER UPLO
178: INTEGER INFO, LDA, LDB, LWORK, N, NRHS
179: * ..
180: * .. Array Arguments ..
181: INTEGER IPIV( * )
182: COMPLEX*16 A( LDA, * ), B( LDB, * ), WORK( * )
183: * ..
184: *
185: * =====================================================================
186: *
187: * .. Local Scalars ..
188: LOGICAL LQUERY
189: INTEGER LWKOPT, NB
190: * ..
191: * .. External Functions ..
192: LOGICAL LSAME
193: INTEGER ILAENV
194: EXTERNAL LSAME, ILAENV
195: * ..
196: * .. External Subroutines ..
1.9 bertrand 197: EXTERNAL XERBLA, ZHETRF, ZHETRS, ZHETRS2
1.1 bertrand 198: * ..
199: * .. Intrinsic Functions ..
200: INTRINSIC MAX
201: * ..
202: * .. Executable Statements ..
203: *
204: * Test the input parameters.
205: *
206: INFO = 0
207: LQUERY = ( LWORK.EQ.-1 )
208: IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
209: INFO = -1
210: ELSE IF( N.LT.0 ) THEN
211: INFO = -2
212: ELSE IF( NRHS.LT.0 ) THEN
213: INFO = -3
214: ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
215: INFO = -5
216: ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
217: INFO = -8
218: ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
219: INFO = -10
220: END IF
221: *
222: IF( INFO.EQ.0 ) THEN
223: IF( N.EQ.0 ) THEN
224: LWKOPT = 1
225: ELSE
226: NB = ILAENV( 1, 'ZHETRF', UPLO, N, -1, -1, -1 )
227: LWKOPT = N*NB
228: END IF
229: WORK( 1 ) = LWKOPT
230: END IF
231: *
232: IF( INFO.NE.0 ) THEN
233: CALL XERBLA( 'ZHESV ', -INFO )
234: RETURN
235: ELSE IF( LQUERY ) THEN
236: RETURN
237: END IF
238: *
1.9 bertrand 239: * Compute the factorization A = U*D*U**H or A = L*D*L**H.
1.1 bertrand 240: *
241: CALL ZHETRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
242: IF( INFO.EQ.0 ) THEN
243: *
244: * Solve the system A*X = B, overwriting B with X.
245: *
1.9 bertrand 246: IF ( LWORK.LT.N ) THEN
247: *
248: * Solve with TRS ( Use Level BLAS 2)
249: *
250: CALL ZHETRS( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )
251: *
252: ELSE
253: *
254: * Solve with TRS2 ( Use Level BLAS 3)
255: *
256: CALL ZHETRS2( UPLO,N,NRHS,A,LDA,IPIV,B,LDB,WORK,INFO )
257: *
258: END IF
1.1 bertrand 259: *
260: END IF
261: *
262: WORK( 1 ) = LWKOPT
263: *
264: RETURN
265: *
266: * End of ZHESV
267: *
268: END
CVSweb interface <joel.bertrand@systella.fr>