LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zerrtr.f
Go to the documentation of this file.
1*> \brief \b ZERRTR
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 ZERRTR( 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*> ZERRTR tests the error exits for the COMPLEX*16 triangular routines.
25*> \endverbatim
26*
27* Arguments:
28* ==========
29*
30*> \param[in] PATH
31*> \verbatim
32*> PATH is CHARACTER*3
33*> The LAPACK path name for the routines to be tested.
34*> \endverbatim
35*>
36*> \param[in] NUNIT
37*> \verbatim
38*> NUNIT is INTEGER
39*> The unit number for output.
40*> \endverbatim
41*
42* Authors:
43* ========
44*
45*> \author Univ. of Tennessee
46*> \author Univ. of California Berkeley
47*> \author Univ. of Colorado Denver
48*> \author NAG Ltd.
49*
50*> \ingroup complex16_lin
51*
52* =====================================================================
53 SUBROUTINE zerrtr( PATH, NUNIT )
54*
55* -- LAPACK test routine --
56* -- LAPACK is a software package provided by Univ. of Tennessee, --
57* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
58*
59* .. Scalar Arguments ..
60 CHARACTER*3 PATH
61 INTEGER NUNIT
62* ..
63*
64* =====================================================================
65*
66* .. Parameters ..
67 INTEGER NMAX
68 parameter( nmax = 2 )
69* ..
70* .. Local Scalars ..
71 CHARACTER*2 C2
72 INTEGER INFO
73 DOUBLE PRECISION RCOND, SCALE, SCALES(0)
74* ..
75* .. Local Arrays ..
76 DOUBLE PRECISION R1( NMAX ), R2( NMAX ), RW( NMAX )
77 COMPLEX*16 A( NMAX, NMAX ), B( NMAX ), W( NMAX ),
78 $ X( NMAX )
79* ..
80* .. External Functions ..
81 LOGICAL LSAMEN
82 EXTERNAL lsamen
83* ..
84* .. External Subroutines ..
85 EXTERNAL alaesm, chkxer, zlatbs, zlatps, zlatrs,
88 $ ztrtri, ztrtrs
89* ..
90* .. Scalars in Common ..
91 LOGICAL LERR, OK
92 CHARACTER*32 SRNAMT
93 INTEGER INFOT, NOUT
94* ..
95* .. Common blocks ..
96 COMMON / infoc / infot, nout, ok, lerr
97 COMMON / srnamc / srnamt
98* ..
99* .. Executable Statements ..
100*
101 nout = nunit
102 WRITE( nout, fmt = * )
103 c2 = path( 2: 3 )
104 a( 1, 1 ) = 1.d0
105 a( 1, 2 ) = 2.d0
106 a( 2, 2 ) = 3.d0
107 a( 2, 1 ) = 4.d0
108 ok = .true.
109*
110* Test error exits for the general triangular routines.
111*
112 IF( lsamen( 2, c2, 'TR' ) ) THEN
113*
114* ZTRTRI
115*
116 srnamt = 'ZTRTRI'
117 infot = 1
118 CALL ztrtri( '/', 'N', 0, a, 1, info )
119 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
120 infot = 2
121 CALL ztrtri( 'U', '/', 0, a, 1, info )
122 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
123 infot = 3
124 CALL ztrtri( 'U', 'N', -1, a, 1, info )
125 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
126 infot = 5
127 CALL ztrtri( 'U', 'N', 2, a, 1, info )
128 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
129*
130* ZTRTI2
131*
132 srnamt = 'ZTRTI2'
133 infot = 1
134 CALL ztrti2( '/', 'N', 0, a, 1, info )
135 CALL chkxer( 'ZTRTI2', infot, nout, lerr, ok )
136 infot = 2
137 CALL ztrti2( 'U', '/', 0, a, 1, info )
138 CALL chkxer( 'ZTRTI2', infot, nout, lerr, ok )
139 infot = 3
140 CALL ztrti2( 'U', 'N', -1, a, 1, info )
141 CALL chkxer( 'ZTRTI2', infot, nout, lerr, ok )
142 infot = 5
143 CALL ztrti2( 'U', 'N', 2, a, 1, info )
144 CALL chkxer( 'ZTRTI2', infot, nout, lerr, ok )
145*
146*
147* ZTRTRS
148*
149 srnamt = 'ZTRTRS'
150 infot = 1
151 CALL ztrtrs( '/', 'N', 'N', 0, 0, a, 1, x, 1, info )
152 CALL chkxer( 'ZTRTRS', infot, nout, lerr, ok )
153 infot = 2
154 CALL ztrtrs( 'U', '/', 'N', 0, 0, a, 1, x, 1, info )
155 CALL chkxer( 'ZTRTRS', infot, nout, lerr, ok )
156 infot = 3
157 CALL ztrtrs( 'U', 'N', '/', 0, 0, a, 1, x, 1, info )
158 CALL chkxer( 'ZTRTRS', infot, nout, lerr, ok )
159 infot = 4
160 CALL ztrtrs( 'U', 'N', 'N', -1, 0, a, 1, x, 1, info )
161 CALL chkxer( 'ZTRTRS', infot, nout, lerr, ok )
162 infot = 5
163 CALL ztrtrs( 'U', 'N', 'N', 0, -1, a, 1, x, 1, info )
164 CALL chkxer( 'ZTRTRS', infot, nout, lerr, ok )
165 infot = 7
166*
167* ZTRRFS
168*
169 srnamt = 'ZTRRFS'
170 infot = 1
171 CALL ztrrfs( '/', 'N', 'N', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
172 $ rw, info )
173 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
174 infot = 2
175 CALL ztrrfs( 'U', '/', 'N', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
176 $ rw, info )
177 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
178 infot = 3
179 CALL ztrrfs( 'U', 'N', '/', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
180 $ rw, info )
181 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
182 infot = 4
183 CALL ztrrfs( 'U', 'N', 'N', -1, 0, a, 1, b, 1, x, 1, r1, r2, w,
184 $ rw, info )
185 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
186 infot = 5
187 CALL ztrrfs( 'U', 'N', 'N', 0, -1, a, 1, b, 1, x, 1, r1, r2, w,
188 $ rw, info )
189 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
190 infot = 7
191 CALL ztrrfs( 'U', 'N', 'N', 2, 1, a, 1, b, 2, x, 2, r1, r2, w,
192 $ rw, info )
193 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
194 infot = 9
195 CALL ztrrfs( 'U', 'N', 'N', 2, 1, a, 2, b, 1, x, 2, r1, r2, w,
196 $ rw, info )
197 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
198 infot = 11
199 CALL ztrrfs( 'U', 'N', 'N', 2, 1, a, 2, b, 2, x, 1, r1, r2, w,
200 $ rw, info )
201 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
202*
203* ZTRCON
204*
205 srnamt = 'ZTRCON'
206 infot = 1
207 CALL ztrcon( '/', 'U', 'N', 0, a, 1, rcond, w, rw, info )
208 CALL chkxer( 'ZTRCON', infot, nout, lerr, ok )
209 infot = 2
210 CALL ztrcon( '1', '/', 'N', 0, a, 1, rcond, w, rw, info )
211 CALL chkxer( 'ZTRCON', infot, nout, lerr, ok )
212 infot = 3
213 CALL ztrcon( '1', 'U', '/', 0, a, 1, rcond, w, rw, info )
214 CALL chkxer( 'ZTRCON', infot, nout, lerr, ok )
215 infot = 4
216 CALL ztrcon( '1', 'U', 'N', -1, a, 1, rcond, w, rw, info )
217 CALL chkxer( 'ZTRCON', infot, nout, lerr, ok )
218 infot = 6
219 CALL ztrcon( '1', 'U', 'N', 2, a, 1, rcond, w, rw, info )
220 CALL chkxer( 'ZTRCON', infot, nout, lerr, ok )
221*
222* ZLATRS
223*
224 srnamt = 'ZLATRS'
225 infot = 1
226 CALL zlatrs( '/', 'N', 'N', 'N', 0, a, 1, x, scale, rw, info )
227 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
228 infot = 2
229 CALL zlatrs( 'U', '/', 'N', 'N', 0, a, 1, x, scale, rw, info )
230 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
231 infot = 3
232 CALL zlatrs( 'U', 'N', '/', 'N', 0, a, 1, x, scale, rw, info )
233 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
234 infot = 4
235 CALL zlatrs( 'U', 'N', 'N', '/', 0, a, 1, x, scale, rw, info )
236 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
237 infot = 5
238 CALL zlatrs( 'U', 'N', 'N', 'N', -1, a, 1, x, scale, rw, info )
239 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
240 infot = 7
241 CALL zlatrs( 'U', 'N', 'N', 'N', 2, a, 1, x, scale, rw, info )
242 CALL chkxer( 'ZLATRS', infot, nout, lerr, ok )
243*
244* ZLATRS3
245*
246 srnamt = 'ZLATRS3'
247 infot = 1
248 CALL zlatrs3( '/', 'N', 'N', 'N', 0, 0, a, 1, x, 1, scales,
249 $ rw, rw( 2 ), 1, info )
250 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
251 infot = 2
252 CALL zlatrs3( 'U', '/', 'N', 'N', 0, 0, a, 1, x, 1, scales,
253 $ rw, rw( 2 ), 1, info )
254 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
255 infot = 3
256 CALL zlatrs3( 'U', 'N', '/', 'N', 0, 0, a, 1, x, 1, scales,
257 $ rw, rw( 2 ), 1, info )
258 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
259 infot = 4
260 CALL zlatrs3( 'U', 'N', 'N', '/', 0, 0, a, 1, x, 1, scales,
261 $ rw, rw( 2 ), 1, info )
262 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
263 infot = 5
264 CALL zlatrs3( 'U', 'N', 'N', 'N', -1, 0, a, 1, x, 1, scales,
265 $ rw, rw( 2 ), 1, info )
266 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
267 infot = 6
268 CALL zlatrs3( 'U', 'N', 'N', 'N', 0, -1, a, 1, x, 1, scales,
269 $ rw, rw( 2 ), 1, info )
270 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
271 infot = 8
272 CALL zlatrs3( 'U', 'N', 'N', 'N', 2, 0, a, 1, x, 1, scales,
273 $ rw, rw( 2 ), 1, info )
274 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
275 infot = 10
276 CALL zlatrs3( 'U', 'N', 'N', 'N', 2, 0, a, 2, x, 1, scales,
277 $ rw, rw( 2 ), 1, info )
278 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
279 infot = 14
280 CALL zlatrs3( 'U', 'N', 'N', 'N', 1, 0, a, 1, x, 1, scales,
281 $ rw, rw( 2 ), 0, info )
282 CALL chkxer( 'ZLATRS3', infot, nout, lerr, ok )
283*
284* Test error exits for the packed triangular routines.
285*
286 ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
287*
288* ZTPTRI
289*
290 srnamt = 'ZTPTRI'
291 infot = 1
292 CALL ztptri( '/', 'N', 0, a, info )
293 CALL chkxer( 'ZTPTRI', infot, nout, lerr, ok )
294 infot = 2
295 CALL ztptri( 'U', '/', 0, a, info )
296 CALL chkxer( 'ZTPTRI', infot, nout, lerr, ok )
297 infot = 3
298 CALL ztptri( 'U', 'N', -1, a, info )
299 CALL chkxer( 'ZTPTRI', infot, nout, lerr, ok )
300*
301* ZTPTRS
302*
303 srnamt = 'ZTPTRS'
304 infot = 1
305 CALL ztptrs( '/', 'N', 'N', 0, 0, a, x, 1, info )
306 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
307 infot = 2
308 CALL ztptrs( 'U', '/', 'N', 0, 0, a, x, 1, info )
309 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
310 infot = 3
311 CALL ztptrs( 'U', 'N', '/', 0, 0, a, x, 1, info )
312 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
313 infot = 4
314 CALL ztptrs( 'U', 'N', 'N', -1, 0, a, x, 1, info )
315 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
316 infot = 5
317 CALL ztptrs( 'U', 'N', 'N', 0, -1, a, x, 1, info )
318 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
319 infot = 8
320 CALL ztptrs( 'U', 'N', 'N', 2, 1, a, x, 1, info )
321 CALL chkxer( 'ZTPTRS', infot, nout, lerr, ok )
322*
323* ZTPRFS
324*
325 srnamt = 'ZTPRFS'
326 infot = 1
327 CALL ztprfs( '/', 'N', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, rw,
328 $ info )
329 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
330 infot = 2
331 CALL ztprfs( 'U', '/', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, rw,
332 $ info )
333 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
334 infot = 3
335 CALL ztprfs( 'U', 'N', '/', 0, 0, a, b, 1, x, 1, r1, r2, w, rw,
336 $ info )
337 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
338 infot = 4
339 CALL ztprfs( 'U', 'N', 'N', -1, 0, a, b, 1, x, 1, r1, r2, w,
340 $ rw, info )
341 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
342 infot = 5
343 CALL ztprfs( 'U', 'N', 'N', 0, -1, a, b, 1, x, 1, r1, r2, w,
344 $ rw, info )
345 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
346 infot = 8
347 CALL ztprfs( 'U', 'N', 'N', 2, 1, a, b, 1, x, 2, r1, r2, w, rw,
348 $ info )
349 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
350 infot = 10
351 CALL ztprfs( 'U', 'N', 'N', 2, 1, a, b, 2, x, 1, r1, r2, w, rw,
352 $ info )
353 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
354*
355* ZTPCON
356*
357 srnamt = 'ZTPCON'
358 infot = 1
359 CALL ztpcon( '/', 'U', 'N', 0, a, rcond, w, rw, info )
360 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
361 infot = 2
362 CALL ztpcon( '1', '/', 'N', 0, a, rcond, w, rw, info )
363 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
364 infot = 3
365 CALL ztpcon( '1', 'U', '/', 0, a, rcond, w, rw, info )
366 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
367 infot = 4
368 CALL ztpcon( '1', 'U', 'N', -1, a, rcond, w, rw, info )
369 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
370*
371* ZLATPS
372*
373 srnamt = 'ZLATPS'
374 infot = 1
375 CALL zlatps( '/', 'N', 'N', 'N', 0, a, x, scale, rw, info )
376 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
377 infot = 2
378 CALL zlatps( 'U', '/', 'N', 'N', 0, a, x, scale, rw, info )
379 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
380 infot = 3
381 CALL zlatps( 'U', 'N', '/', 'N', 0, a, x, scale, rw, info )
382 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
383 infot = 4
384 CALL zlatps( 'U', 'N', 'N', '/', 0, a, x, scale, rw, info )
385 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
386 infot = 5
387 CALL zlatps( 'U', 'N', 'N', 'N', -1, a, x, scale, rw, info )
388 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
389*
390* Test error exits for the banded triangular routines.
391*
392 ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
393*
394* ZTBTRS
395*
396 srnamt = 'ZTBTRS'
397 infot = 1
398 CALL ztbtrs( '/', 'N', 'N', 0, 0, 0, a, 1, x, 1, info )
399 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
400 infot = 2
401 CALL ztbtrs( 'U', '/', 'N', 0, 0, 0, a, 1, x, 1, info )
402 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
403 infot = 3
404 CALL ztbtrs( 'U', 'N', '/', 0, 0, 0, a, 1, x, 1, info )
405 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
406 infot = 4
407 CALL ztbtrs( 'U', 'N', 'N', -1, 0, 0, a, 1, x, 1, info )
408 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
409 infot = 5
410 CALL ztbtrs( 'U', 'N', 'N', 0, -1, 0, a, 1, x, 1, info )
411 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
412 infot = 6
413 CALL ztbtrs( 'U', 'N', 'N', 0, 0, -1, a, 1, x, 1, info )
414 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
415 infot = 8
416 CALL ztbtrs( 'U', 'N', 'N', 2, 1, 1, a, 1, x, 2, info )
417 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
418 infot = 10
419 CALL ztbtrs( 'U', 'N', 'N', 2, 0, 1, a, 1, x, 1, info )
420 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
421*
422* ZTBRFS
423*
424 srnamt = 'ZTBRFS'
425 infot = 1
426 CALL ztbrfs( '/', 'N', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
427 $ w, rw, info )
428 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
429 infot = 2
430 CALL ztbrfs( 'U', '/', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
431 $ w, rw, info )
432 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
433 infot = 3
434 CALL ztbrfs( 'U', 'N', '/', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
435 $ w, rw, info )
436 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
437 infot = 4
438 CALL ztbrfs( 'U', 'N', 'N', -1, 0, 0, a, 1, b, 1, x, 1, r1, r2,
439 $ w, rw, info )
440 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
441 infot = 5
442 CALL ztbrfs( 'U', 'N', 'N', 0, -1, 0, a, 1, b, 1, x, 1, r1, r2,
443 $ w, rw, info )
444 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
445 infot = 6
446 CALL ztbrfs( 'U', 'N', 'N', 0, 0, -1, a, 1, b, 1, x, 1, r1, r2,
447 $ w, rw, info )
448 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
449 infot = 8
450 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 1, b, 2, x, 2, r1, r2,
451 $ w, rw, info )
452 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
453 infot = 10
454 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 1, x, 2, r1, r2,
455 $ w, rw, info )
456 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
457 infot = 12
458 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 2, x, 1, r1, r2,
459 $ w, rw, info )
460 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
461*
462* ZTBCON
463*
464 srnamt = 'ZTBCON'
465 infot = 1
466 CALL ztbcon( '/', 'U', 'N', 0, 0, a, 1, rcond, w, rw, info )
467 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
468 infot = 2
469 CALL ztbcon( '1', '/', 'N', 0, 0, a, 1, rcond, w, rw, info )
470 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
471 infot = 3
472 CALL ztbcon( '1', 'U', '/', 0, 0, a, 1, rcond, w, rw, info )
473 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
474 infot = 4
475 CALL ztbcon( '1', 'U', 'N', -1, 0, a, 1, rcond, w, rw, info )
476 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
477 infot = 5
478 CALL ztbcon( '1', 'U', 'N', 0, -1, a, 1, rcond, w, rw, info )
479 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
480 infot = 7
481 CALL ztbcon( '1', 'U', 'N', 2, 1, a, 1, rcond, w, rw, info )
482 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
483*
484* ZLATBS
485*
486 srnamt = 'ZLATBS'
487 infot = 1
488 CALL zlatbs( '/', 'N', 'N', 'N', 0, 0, a, 1, x, scale, rw,
489 $ info )
490 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
491 infot = 2
492 CALL zlatbs( 'U', '/', 'N', 'N', 0, 0, a, 1, x, scale, rw,
493 $ info )
494 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
495 infot = 3
496 CALL zlatbs( 'U', 'N', '/', 'N', 0, 0, a, 1, x, scale, rw,
497 $ info )
498 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
499 infot = 4
500 CALL zlatbs( 'U', 'N', 'N', '/', 0, 0, a, 1, x, scale, rw,
501 $ info )
502 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
503 infot = 5
504 CALL zlatbs( 'U', 'N', 'N', 'N', -1, 0, a, 1, x, scale, rw,
505 $ info )
506 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
507 infot = 6
508 CALL zlatbs( 'U', 'N', 'N', 'N', 1, -1, a, 1, x, scale, rw,
509 $ info )
510 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
511 infot = 8
512 CALL zlatbs( 'U', 'N', 'N', 'N', 2, 1, a, 1, x, scale, rw,
513 $ info )
514 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
515 END IF
516*
517* Print a summary line.
518*
519 CALL alaesm( path, ok, nout )
520*
521 RETURN
522*
523* End of ZERRTR
524*
525 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine zlatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)
ZLATBS solves a triangular banded system of equations.
Definition zlatbs.f:243
subroutine zlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
ZLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition zlatps.f:231
subroutine zlatrs3(uplo, trans, diag, normin, n, nrhs, a, lda, x, ldx, scale, cnorm, work, lwork, info)
ZLATRS3 solves a triangular system of equations with the scale factors set to prevent overflow.
Definition zlatrs3.f:230
subroutine zlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
ZLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition zlatrs.f:239
subroutine ztbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, rwork, info)
ZTBCON
Definition ztbcon.f:143
subroutine ztbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZTBRFS
Definition ztbrfs.f:188
subroutine ztbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)
ZTBTRS
Definition ztbtrs.f:146
subroutine ztpcon(norm, uplo, diag, n, ap, rcond, work, rwork, info)
ZTPCON
Definition ztpcon.f:130
subroutine ztprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZTPRFS
Definition ztprfs.f:174
subroutine ztptri(uplo, diag, n, ap, info)
ZTPTRI
Definition ztptri.f:117
subroutine ztptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)
ZTPTRS
Definition ztptrs.f:130
subroutine ztrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)
ZTRCON
Definition ztrcon.f:137
subroutine ztrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZTRRFS
Definition ztrrfs.f:182
subroutine ztrti2(uplo, diag, n, a, lda, info)
ZTRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
Definition ztrti2.f:110
subroutine ztrtri(uplo, diag, n, a, lda, info)
ZTRTRI
Definition ztrtri.f:109
subroutine ztrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
ZTRTRS
Definition ztrtrs.f:140
subroutine zerrtr(path, nunit)
ZERRTR
Definition zerrtr.f:54