OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zerrpo.f
Go to the documentation of this file.
1*> \brief \b ZERRPO
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE ZERRPO( PATH, NUNIT )
12*
13* .. Scalar Arguments ..
14* CHARACTER*3 PATH
15* INTEGER NUNIT
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> ZERRPO tests the error exits for the COMPLEX*16 routines
25*> for Hermitian positive definite matrices.
26*> \endverbatim
27*
28* Arguments:
29* ==========
30*
31*> \param[in] PATH
32*> \verbatim
33*> PATH is CHARACTER*3
34*> The LAPACK path name for the routines to be tested.
35*> \endverbatim
36*>
37*> \param[in] NUNIT
38*> \verbatim
39*> NUNIT is INTEGER
40*> The unit number for output.
41*> \endverbatim
42*
43* Authors:
44* ========
45*
46*> \author Univ. of Tennessee
47*> \author Univ. of California Berkeley
48*> \author Univ. of Colorado Denver
49*> \author NAG Ltd.
50*
51*> \ingroup complex16_lin
52*
53* =====================================================================
54 SUBROUTINE zerrpo( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70* ..
71* .. Local Scalars ..
72 CHARACTER*2 C2
73 INTEGER I, INFO, J
74 DOUBLE PRECISION ANRM, RCOND
75* ..
76* .. Local Arrays ..
77 DOUBLE PRECISION R( NMAX ), R1( NMAX ), R2( NMAX )
78 COMPLEX*16 A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
79 $ W( 2*NMAX ), X( NMAX )
80* ..
81* .. External Functions ..
82 LOGICAL LSAMEN
83 EXTERNAL lsamen
84* ..
85* .. External Subroutines ..
86 EXTERNAL alaesm, chkxer, zpbcon, zpbequ, zpbrfs, zpbtf2,
90* ..
91* .. Scalars in Common ..
92 LOGICAL LERR, OK
93 CHARACTER*32 SRNAMT
94 INTEGER INFOT, NOUT
95* ..
96* .. Common blocks ..
97 COMMON / infoc / infot, nout, ok, lerr
98 COMMON / srnamc / srnamt
99* ..
100* .. Intrinsic Functions ..
101 INTRINSIC dble, dcmplx
102* ..
103* .. Executable Statements ..
104*
105 nout = nunit
106 WRITE( nout, fmt = * )
107 c2 = path( 2: 3 )
108*
109* Set the variables to innocuous values.
110*
111 DO 20 j = 1, nmax
112 DO 10 i = 1, nmax
113 a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
114 $ -1.d0 / dble( i+j ) )
115 af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
116 $ -1.d0 / dble( i+j ) )
117 10 CONTINUE
118 b( j ) = 0.d0
119 r1( j ) = 0.d0
120 r2( j ) = 0.d0
121 w( j ) = 0.d0
122 x( j ) = 0.d0
123 20 CONTINUE
124 anrm = 1.d0
125 ok = .true.
126*
127* Test error exits of the routines that use the Cholesky
128* decomposition of a Hermitian positive definite matrix.
129*
130 IF( lsamen( 2, c2, 'PO' ) ) THEN
131*
132* ZPOTRF
133*
134 srnamt = 'ZPOTRF'
135 infot = 1
136 CALL zpotrf( '/', 0, a, 1, info )
137 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
138 infot = 2
139 CALL zpotrf( 'U', -1, a, 1, info )
140 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
141 infot = 4
142 CALL zpotrf( 'U', 2, a, 1, info )
143 CALL chkxer( 'ZPOTRF', infot, nout, lerr, ok )
144*
145* ZPOTF2
146*
147 srnamt = 'ZPOTF2'
148 infot = 1
149 CALL zpotf2( '/', 0, a, 1, info )
150 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
151 infot = 2
152 CALL zpotf2( 'U', -1, a, 1, info )
153 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
154 infot = 4
155 CALL zpotf2( 'U', 2, a, 1, info )
156 CALL chkxer( 'ZPOTF2', infot, nout, lerr, ok )
157*
158* ZPOTRI
159*
160 srnamt = 'ZPOTRI'
161 infot = 1
162 CALL zpotri( '/', 0, a, 1, info )
163 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
164 infot = 2
165 CALL zpotri( 'U', -1, a, 1, info )
166 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
167 infot = 4
168 CALL zpotri( 'U', 2, a, 1, info )
169 CALL chkxer( 'ZPOTRI', infot, nout, lerr, ok )
170*
171* ZPOTRS
172*
173 srnamt = 'ZPOTRS'
174 infot = 1
175 CALL zpotrs( '/', 0, 0, a, 1, b, 1, info )
176 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
177 infot = 2
178 CALL zpotrs( 'U', -1, 0, a, 1, b, 1, info )
179 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
180 infot = 3
181 CALL zpotrs( 'U', 0, -1, a, 1, b, 1, info )
182 CALL chkxer( 'zpotrs', INFOT, NOUT, LERR, OK )
183 INFOT = 5
184 CALL ZPOTRS( 'u', 2, 1, A, 1, B, 2, INFO )
185 CALL CHKXER( 'zpotrs', infot, nout, lerr, ok )
186 infot = 7
187 CALL zpotrs( 'U', 2, 1, a, 2, b, 1, info )
188 CALL chkxer( 'ZPOTRS', infot, nout, lerr, ok )
189*
190* ZPORFS
191*
192 srnamt = 'ZPORFS'
193 infot = 1
194 CALL zporfs( '/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
195 $ info )
196 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
197 infot = 2
198 CALL zporfs( 'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
199 $ info )
200 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
201 infot = 3
202 CALL zporfs( 'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
203 $ info )
204 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
205 infot = 5
206 CALL zporfs( 'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
207 $ info )
208 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
209 infot = 7
210 CALL zporfs( 'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
211 $ info )
212 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
213 infot = 9
214 CALL zporfs( 'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
215 $ info )
216 CALL chkxer( 'ZPORFS', infot, nout, lerr, ok )
217 infot = 11
218 CALL zporfs( 'u', 2, 1, A, 2, AF, 2, B, 2, X, 1, R1, R2, W, R,
219 $ INFO )
220 CALL CHKXER( 'zporfs', INFOT, NOUT, LERR, OK )
221*
222* ZPOCON
223*
224 SRNAMT = 'zpocon'
225 INFOT = 1
226 CALL ZPOCON( '/', 0, A, 1, ANRM, RCOND, W, R, INFO )
227 CALL CHKXER( 'zpocon', INFOT, NOUT, LERR, OK )
228 INFOT = 2
229 CALL ZPOCON( 'u', -1, A, 1, ANRM, RCOND, W, R, INFO )
230 CALL CHKXER( 'zpocon', INFOT, NOUT, LERR, OK )
231 INFOT = 4
232 CALL ZPOCON( 'u', 2, A, 1, ANRM, RCOND, W, R, INFO )
233 CALL CHKXER( 'zpocon', INFOT, NOUT, LERR, OK )
234 INFOT = 5
235 CALL ZPOCON( 'u', 1, A, 1, -ANRM, RCOND, W, R, INFO )
236 CALL CHKXER( 'zpocon', INFOT, NOUT, LERR, OK )
237*
238* ZPOEQU
239*
240 SRNAMT = 'zpoequ'
241 INFOT = 1
242 CALL ZPOEQU( -1, A, 1, R1, RCOND, ANRM, INFO )
243 CALL CHKXER( 'zpoequ', INFOT, NOUT, LERR, OK )
244 INFOT = 3
245 CALL ZPOEQU( 2, A, 1, R1, RCOND, ANRM, INFO )
246 CALL CHKXER( 'zpoequ', INFOT, NOUT, LERR, OK )
247*
248* Test error exits of the routines that use the Cholesky
249* decomposition of a Hermitian positive definite packed matrix.
250*
251 ELSE IF( LSAMEN( 2, C2, 'pp' ) ) THEN
252*
253* ZPPTRF
254*
255 SRNAMT = 'zpptrf'
256 INFOT = 1
257 CALL ZPPTRF( '/', 0, A, INFO )
258 CALL CHKXER( 'zpptrf', INFOT, NOUT, LERR, OK )
259 INFOT = 2
260 CALL ZPPTRF( 'u', -1, A, INFO )
261 CALL CHKXER( 'zpptrf', INFOT, NOUT, LERR, OK )
262*
263* ZPPTRI
264*
265 SRNAMT = 'zpptri'
266 INFOT = 1
267 CALL ZPPTRI( '/', 0, A, INFO )
268 CALL CHKXER( 'zpptri', INFOT, NOUT, LERR, OK )
269 INFOT = 2
270 CALL ZPPTRI( 'u', -1, A, INFO )
271 CALL CHKXER( 'zpptri', INFOT, NOUT, LERR, OK )
272*
273* ZPPTRS
274*
275 SRNAMT = 'zpptrs'
276 INFOT = 1
277 CALL ZPPTRS( '/', 0, 0, A, B, 1, INFO )
278 CALL CHKXER( 'zpptrs', INFOT, NOUT, LERR, OK )
279 INFOT = 2
280 CALL ZPPTRS( 'u', -1, 0, A, B, 1, INFO )
281 CALL CHKXER( 'zpptrs', INFOT, NOUT, LERR, OK )
282 INFOT = 3
283 CALL ZPPTRS( 'u', 0, -1, A, B, 1, INFO )
284 CALL CHKXER( 'zpptrs', INFOT, NOUT, LERR, OK )
285 INFOT = 6
286 CALL ZPPTRS( 'u', 2, 1, A, B, 1, INFO )
287 CALL CHKXER( 'zpptrs', INFOT, NOUT, LERR, OK )
288*
289* ZPPRFS
290*
291 SRNAMT = 'zpprfs'
292 INFOT = 1
293 CALL ZPPRFS( '/', 0, 0, A, AF, B, 1, X, 1, R1, R2, W, R, INFO )
294 CALL CHKXER( 'zpprfs', INFOT, NOUT, LERR, OK )
295 INFOT = 2
296 CALL ZPPRFS( 'u', -1, 0, A, AF, B, 1, X, 1, R1, R2, W, R,
297 $ INFO )
298 CALL CHKXER( 'zpprfs', INFOT, NOUT, LERR, OK )
299 INFOT = 3
300 CALL ZPPRFS( 'u', 0, -1, A, AF, B, 1, X, 1, R1, R2, W, R,
301 $ INFO )
302 CALL CHKXER( 'zpprfs', INFOT, NOUT, LERR, OK )
303 INFOT = 7
304 CALL ZPPRFS( 'u', 2, 1, A, AF, B, 1, X, 2, R1, R2, W, R, INFO )
305 CALL CHKXER( 'zpprfs', INFOT, NOUT, LERR, OK )
306 INFOT = 9
307 CALL ZPPRFS( 'u', 2, 1, A, AF, B, 2, X, 1, R1, R2, W, R, INFO )
308 CALL CHKXER( 'zpprfs', INFOT, NOUT, LERR, OK )
309*
310* ZPPCON
311*
312 SRNAMT = 'zppcon'
313 INFOT = 1
314 CALL ZPPCON( '/', 0, A, ANRM, RCOND, W, R, INFO )
315 CALL CHKXER( 'zppcon', INFOT, NOUT, LERR, OK )
316 INFOT = 2
317 CALL ZPPCON( 'u', -1, A, ANRM, RCOND, W, R, INFO )
318 CALL CHKXER( 'zppcon', INFOT, NOUT, LERR, OK )
319 INFOT = 4
320 CALL ZPPCON( 'u', 1, A, -ANRM, RCOND, W, R, INFO )
321 CALL CHKXER( 'zppcon', INFOT, NOUT, LERR, OK )
322*
323* ZPPEQU
324*
325 SRNAMT = 'zppequ'
326 INFOT = 1
327 CALL ZPPEQU( '/', 0, A, R1, RCOND, ANRM, INFO )
328 CALL CHKXER( 'zppequ', INFOT, NOUT, LERR, OK )
329 INFOT = 2
330 CALL ZPPEQU( 'u', -1, A, R1, RCOND, ANRM, INFO )
331 CALL CHKXER( 'zppequ', INFOT, NOUT, LERR, OK )
332*
333* Test error exits of the routines that use the Cholesky
334* decomposition of a Hermitian positive definite band matrix.
335*
336 ELSE IF( LSAMEN( 2, C2, 'pb' ) ) THEN
337*
338* ZPBTRF
339*
340 SRNAMT = 'zpbtrf'
341 INFOT = 1
342 CALL ZPBTRF( '/', 0, 0, A, 1, INFO )
343 CALL CHKXER( 'zpbtrf', INFOT, NOUT, LERR, OK )
344 INFOT = 2
345 CALL ZPBTRF( 'u', -1, 0, A, 1, INFO )
346 CALL CHKXER( 'zpbtrf', INFOT, NOUT, LERR, OK )
347 INFOT = 3
348 CALL ZPBTRF( 'u', 1, -1, A, 1, INFO )
349 CALL CHKXER( 'zpbtrf', INFOT, NOUT, LERR, OK )
350 INFOT = 5
351 CALL ZPBTRF( 'u', 2, 1, A, 1, INFO )
352 CALL CHKXER( 'zpbtrf', INFOT, NOUT, LERR, OK )
353*
354* ZPBTF2
355*
356 SRNAMT = 'zpbtf2'
357 INFOT = 1
358 CALL ZPBTF2( '/', 0, 0, A, 1, INFO )
359 CALL CHKXER( 'zpbtf2', INFOT, NOUT, LERR, OK )
360 INFOT = 2
361 CALL ZPBTF2( 'u', -1, 0, A, 1, INFO )
362 CALL CHKXER( 'zpbtf2', INFOT, NOUT, LERR, OK )
363 INFOT = 3
364 CALL ZPBTF2( 'u', 1, -1, A, 1, INFO )
365 CALL CHKXER( 'zpbtf2', INFOT, NOUT, LERR, OK )
366 INFOT = 5
367 CALL ZPBTF2( 'u', 2, 1, A, 1, INFO )
368 CALL CHKXER( 'zpbtf2', INFOT, NOUT, LERR, OK )
369*
370* ZPBTRS
371*
372 SRNAMT = 'zpbtrs'
373 INFOT = 1
374 CALL ZPBTRS( '/', 0, 0, 0, A, 1, B, 1, INFO )
375 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
376 INFOT = 2
377 CALL ZPBTRS( 'u', -1, 0, 0, A, 1, B, 1, INFO )
378 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
379 INFOT = 3
380 CALL ZPBTRS( 'u', 1, -1, 0, A, 1, B, 1, INFO )
381 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
382 INFOT = 4
383 CALL ZPBTRS( 'u', 0, 0, -1, A, 1, B, 1, INFO )
384 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
385 INFOT = 6
386 CALL ZPBTRS( 'u', 2, 1, 1, A, 1, B, 1, INFO )
387 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
388 INFOT = 8
389 CALL ZPBTRS( 'u', 2, 0, 1, A, 1, B, 1, INFO )
390 CALL CHKXER( 'zpbtrs', INFOT, NOUT, LERR, OK )
391*
392* ZPBRFS
393*
394 SRNAMT = 'zpbrfs'
395 INFOT = 1
396 CALL ZPBRFS( '/', 0, 0, 0, A, 1, AF, 1, B, 1, X, 1, R1, R2, W,
397 $ R, INFO )
398 CALL CHKXER( 'zpbrfs', infot, nout, lerr, ok )
399 infot = 2
400 CALL zpbrfs( 'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
401 $ r, info )
402 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
403 infot = 3
404 CALL zpbrfs( 'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
405 $ r, info )
406 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
407 infot = 4
408 CALL zpbrfs( 'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
409 $ r, info )
410 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
411 infot = 6
412 CALL zpbrfs( 'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
413 $ r, info )
414 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
415 infot = 8
416 CALL zpbrfs( 'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
417 $ r, info )
418 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
419 infot = 10
420 CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
421 $ r, info )
422 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
423 infot = 12
424 CALL zpbrfs( 'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
425 $ r, info )
426 CALL chkxer( 'ZPBRFS', infot, nout, lerr, ok )
427*
428* ZPBCON
429*
430 srnamt = 'ZPBCON'
431 infot = 1
432 CALL zpbcon( '/', 0, 0, a, 1, anrm, rcond, w, r, info )
433 CALL chkxer( 'ZPBCON', infot, nout, lerr, ok )
434 infot = 2
435 CALL zpbcon( 'U', -1, 0, a, 1, anrm, rcond, w, r, info )
436 CALL chkxer( 'zpbcon', INFOT, NOUT, LERR, OK )
437 INFOT = 3
438 CALL ZPBCON( 'u', 1, -1, A, 1, ANRM, RCOND, W, R, INFO )
439 CALL CHKXER( 'zpbcon', INFOT, NOUT, LERR, OK )
440 INFOT = 5
441 CALL ZPBCON( 'u', 2, 1, A, 1, ANRM, RCOND, W, R, INFO )
442 CALL CHKXER( 'zpbcon', INFOT, NOUT, LERR, OK )
443 INFOT = 6
444 CALL ZPBCON( 'u', 1, 0, A, 1, -ANRM, RCOND, W, R, INFO )
445 CALL CHKXER( 'zpbcon', INFOT, NOUT, LERR, OK )
446*
447* ZPBEQU
448*
449 SRNAMT = 'zpbequ'
450 INFOT = 1
451 CALL ZPBEQU( '/', 0, 0, A, 1, R1, RCOND, ANRM, INFO )
452 CALL CHKXER( 'zpbequ', INFOT, NOUT, LERR, OK )
453 INFOT = 2
454 CALL ZPBEQU( 'u', -1, 0, A, 1, R1, RCOND, ANRM, INFO )
455 CALL CHKXER( 'zpbequ', INFOT, NOUT, LERR, OK )
456 INFOT = 3
457 CALL ZPBEQU( 'u', 1, -1, A, 1, R1, RCOND, ANRM, INFO )
458 CALL CHKXER( 'zpbequ', INFOT, NOUT, LERR, OK )
459 INFOT = 5
460 CALL ZPBEQU( 'u', 2, 1, A, 1, R1, RCOND, ANRM, INFO )
461 CALL CHKXER( 'zpbequ', INFOT, NOUT, LERR, OK )
462 END IF
463*
464* Print a summary line.
465*
466 CALL ALAESM( PATH, OK, NOUT )
467*
468 RETURN
469*
470* End of ZERRPO
471*
472 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine zpbtrs(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
ZPBTRS
Definition zpbtrs.f:121
subroutine zpbtrf(uplo, n, kd, ab, ldab, info)
ZPBTRF
Definition zpbtrf.f:142
subroutine zpptrs(uplo, n, nrhs, ap, b, ldb, info)
ZPPTRS
Definition zpptrs.f:108
subroutine zpbcon(uplo, n, kd, ab, ldab, anorm, rcond, work, rwork, info)
ZPBCON
Definition zpbcon.f:133
subroutine zppequ(uplo, n, ap, s, scond, amax, info)
ZPPEQU
Definition zppequ.f:117
subroutine zpbequ(uplo, n, kd, ab, ldab, s, scond, amax, info)
ZPBEQU
Definition zpbequ.f:130
subroutine zpprfs(uplo, n, nrhs, ap, afp, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPPRFS
Definition zpprfs.f:171
subroutine zpbtf2(uplo, n, kd, ab, ldab, info)
ZPBTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite band matrix (un...
Definition zpbtf2.f:142
subroutine zppcon(uplo, n, ap, anorm, rcond, work, rwork, info)
ZPPCON
Definition zppcon.f:118
subroutine zpptri(uplo, n, ap, info)
ZPPTRI
Definition zpptri.f:93
subroutine zpbrfs(uplo, n, kd, nrhs, ab, ldab, afb, ldafb, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPBRFS
Definition zpbrfs.f:189
subroutine zpptrf(uplo, n, ap, info)
ZPPTRF
Definition zpptrf.f:119
subroutine zpotf2(uplo, n, a, lda, info)
ZPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
Definition zpotf2.f:109
subroutine zpocon(uplo, n, a, lda, anorm, rcond, work, rwork, info)
ZPOCON
Definition zpocon.f:121
subroutine zporfs(uplo, n, nrhs, a, lda, af, ldaf, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZPORFS
Definition zporfs.f:183
subroutine zpoequ(n, a, lda, s, scond, amax, info)
ZPOEQU
Definition zpoequ.f:113
subroutine zpotri(uplo, n, a, lda, info)
ZPOTRI
Definition zpotri.f:95
subroutine zpotrs(uplo, n, nrhs, a, lda, b, ldb, info)
ZPOTRS
Definition zpotrs.f:110
subroutine zerrpo(path, nunit)
ZERRPO
Definition zerrpo.f:55
subroutine zpotrf(uplo, n, a, lda, info)
ZPOTRF VARIANT: right looking block version of the algorithm, calling Level 3 BLAS.
Definition zpotrf.f:102