OpenRadioss 2025.1.11
OpenRadioss project
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
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, ztbcon,
88* ..
89* .. Scalars in Common ..
90 LOGICAL LERR, OK
91 CHARACTER*32 SRNAMT
92 INTEGER INFOT, NOUT
93* ..
94* .. Common blocks ..
95 COMMON / infoc / infot, nout, ok, lerr
96 COMMON / srnamc / srnamt
97* ..
98* .. Executable Statements ..
99*
100 nout = nunit
101 WRITE( nout, fmt = * )
102 c2 = path( 2: 3 )
103 a( 1, 1 ) = 1.d0
104 a( 1, 2 ) = 2.d0
105 a( 2, 2 ) = 3.d0
106 a( 2, 1 ) = 4.d0
107 ok = .true.
108*
109* Test error exits for the general triangular routines.
110*
111 IF( lsamen( 2, c2, 'TR' ) ) THEN
112*
113* ZTRTRI
114*
115 srnamt = 'ZTRTRI'
116 infot = 1
117 CALL ztrtri( '/', 'N', 0, a, 1, info )
118 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
119 infot = 2
120 CALL ztrtri( 'U', '/', 0, a, 1, info )
121 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
122 infot = 3
123 CALL ztrtri( 'U', 'N', -1, a, 1, info )
124 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
125 infot = 5
126 CALL ztrtri( 'U', 'N', 2, a, 1, info )
127 CALL chkxer( 'ZTRTRI', infot, nout, lerr, ok )
128*
129* ZTRTI2
130*
131 srnamt = 'ZTRTI2'
132 infot = 1
133 CALL ztrti2( '/', 'n', 0, A, 1, INFO )
134 CALL CHKXER( 'ztrti2', INFOT, NOUT, LERR, OK )
135 INFOT = 2
136 CALL ZTRTI2( 'u', '/', 0, A, 1, INFO )
137 CALL CHKXER( 'ztrti2', INFOT, NOUT, LERR, OK )
138 INFOT = 3
139 CALL ZTRTI2( 'u', 'n', -1, A, 1, INFO )
140 CALL CHKXER( 'ztrti2', INFOT, NOUT, LERR, OK )
141 INFOT = 5
142 CALL ZTRTI2( 'u', 'n', 2, A, 1, INFO )
143 CALL CHKXER( 'ztrti2', INFOT, NOUT, LERR, OK )
144*
145*
146* ZTRTRS
147*
148 SRNAMT = 'ztrtrs'
149 INFOT = 1
150 CALL ZTRTRS( '/', 'n', 'n', 0, 0, A, 1, X, 1, INFO )
151 CALL CHKXER( 'ztrtrs', INFOT, NOUT, LERR, OK )
152 INFOT = 2
153 CALL ZTRTRS( 'u', '/', 'n', 0, 0, A, 1, X, 1, INFO )
154 CALL CHKXER( 'ztrtrs', INFOT, NOUT, LERR, OK )
155 INFOT = 3
156 CALL ZTRTRS( 'u', 'n', '/', 0, 0, A, 1, X, 1, INFO )
157 CALL CHKXER( 'ztrtrs', INFOT, NOUT, LERR, OK )
158 INFOT = 4
159 CALL ZTRTRS( 'u', 'n', 'n', -1, 0, A, 1, X, 1, INFO )
160 CALL CHKXER( 'ztrtrs', INFOT, NOUT, LERR, OK )
161 INFOT = 5
162 CALL ZTRTRS( 'u', 'n', 'n', 0, -1, A, 1, X, 1, INFO )
163 CALL CHKXER( 'ztrtrs', INFOT, NOUT, LERR, OK )
164 INFOT = 7
165*
166* ZTRRFS
167*
168 SRNAMT = 'ztrrfs'
169 INFOT = 1
170 CALL ZTRRFS( '/', 'n', 'n', 0, 0, A, 1, B, 1, X, 1, R1, R2, W,
171 $ RW, INFO )
172 CALL CHKXER( 'ztrrfs', INFOT, NOUT, LERR, OK )
173 INFOT = 2
174 CALL ZTRRFS( 'u', '/', 'N', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
175 $ rw, info )
176 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
177 infot = 3
178 CALL ztrrfs( 'U', 'N', '/', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
179 $ rw, info )
180 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
181 infot = 4
182 CALL ztrrfs( 'U', 'N', 'N', -1, 0, a, 1, b, 1, x, 1, r1, r2, w,
183 $ rw, info )
184 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
185 infot = 5
186 CALL ztrrfs( 'U', 'N', 'N', 0, -1, a, 1, b, 1, x, 1, r1, r2, w,
187 $ rw, info )
188 CALL chkxer( 'ZTRRFS', infot, nout, lerr, ok )
189 infot = 7
190 CALL ztrrfs( 'U', 'N', 'N', 2, 1, a, 1, b, 2, x, 2, r1, r2, w,
191 $ rw, info )
192 CALL chkxer( 'ztrrfs', INFOT, NOUT, LERR, OK )
193 INFOT = 9
194 CALL ZTRRFS( 'u', 'n', 'n', 2, 1, A, 2, B, 1, X, 2, R1, R2, W,
195 $ RW, INFO )
196 CALL CHKXER( 'ztrrfs', INFOT, NOUT, LERR, OK )
197 INFOT = 11
198 CALL ZTRRFS( 'u', 'n', 'n', 2, 1, A, 2, B, 2, X, 1, R1, R2, W,
199 $ RW, INFO )
200 CALL CHKXER( 'ztrrfs', INFOT, NOUT, LERR, OK )
201*
202* ZTRCON
203*
204 SRNAMT = 'ztrcon'
205 INFOT = 1
206 CALL ZTRCON( '/', 'u', 'n', 0, A, 1, RCOND, W, RW, INFO )
207 CALL CHKXER( 'ztrcon', INFOT, NOUT, LERR, OK )
208 INFOT = 2
209 CALL ZTRCON( '1', '/', 'n', 0, A, 1, RCOND, W, RW, INFO )
210 CALL CHKXER( 'ztrcon', INFOT, NOUT, LERR, OK )
211 INFOT = 3
212 CALL ZTRCON( '1', 'u', '/', 0, A, 1, RCOND, W, RW, INFO )
213 CALL CHKXER( 'ztrcon', INFOT, NOUT, LERR, OK )
214 INFOT = 4
215 CALL ZTRCON( '1', 'u', 'n', -1, A, 1, RCOND, W, RW, INFO )
216 CALL CHKXER( 'ztrcon', INFOT, NOUT, LERR, OK )
217 INFOT = 6
218 CALL ZTRCON( '1', 'u', 'n', 2, A, 1, RCOND, W, RW, INFO )
219 CALL CHKXER( 'ztrcon', INFOT, NOUT, LERR, OK )
220*
221* ZLATRS
222*
223 SRNAMT = 'zlatrs'
224 INFOT = 1
225 CALL ZLATRS( '/', 'n', 'n', 'n', 0, A, 1, X, SCALE, RW, INFO )
226 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
227 INFOT = 2
228 CALL ZLATRS( 'u', '/', 'n', 'n', 0, A, 1, X, SCALE, RW, INFO )
229 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
230 INFOT = 3
231 CALL ZLATRS( 'u', 'n', '/', 'n', 0, A, 1, X, SCALE, RW, INFO )
232 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
233 INFOT = 4
234 CALL ZLATRS( 'u', 'n', 'n', '/', 0, A, 1, X, SCALE, RW, INFO )
235 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
236 INFOT = 5
237 CALL ZLATRS( 'u', 'n', 'n', 'n', -1, A, 1, X, SCALE, RW, INFO )
238 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
239 INFOT = 7
240 CALL ZLATRS( 'u', 'n', 'n', 'n', 2, A, 1, X, SCALE, RW, INFO )
241 CALL CHKXER( 'zlatrs', INFOT, NOUT, LERR, OK )
242*
243* Test error exits for the packed triangular routines.
244*
245 ELSE IF( LSAMEN( 2, C2, 'tp' ) ) THEN
246*
247* ZTPTRI
248*
249 SRNAMT = 'ztptri'
250 INFOT = 1
251 CALL ZTPTRI( '/', 'n', 0, A, INFO )
252 CALL CHKXER( 'ztptri', INFOT, NOUT, LERR, OK )
253 INFOT = 2
254 CALL ZTPTRI( 'u', '/', 0, A, INFO )
255 CALL CHKXER( 'ztptri', INFOT, NOUT, LERR, OK )
256 INFOT = 3
257 CALL ZTPTRI( 'u', 'n', -1, A, INFO )
258 CALL CHKXER( 'ztptri', INFOT, NOUT, LERR, OK )
259*
260* ZTPTRS
261*
262 SRNAMT = 'ztptrs'
263 INFOT = 1
264 CALL ZTPTRS( '/', 'n', 'n', 0, 0, A, X, 1, INFO )
265 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
266 INFOT = 2
267 CALL ZTPTRS( 'u', '/', 'n', 0, 0, A, X, 1, INFO )
268 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
269 INFOT = 3
270 CALL ZTPTRS( 'u', 'n', '/', 0, 0, A, X, 1, INFO )
271 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
272 INFOT = 4
273 CALL ZTPTRS( 'u', 'n', 'n', -1, 0, A, X, 1, INFO )
274 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
275 INFOT = 5
276 CALL ZTPTRS( 'u', 'n', 'n', 0, -1, A, X, 1, INFO )
277 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
278 INFOT = 8
279 CALL ZTPTRS( 'u', 'n', 'n', 2, 1, A, X, 1, INFO )
280 CALL CHKXER( 'ztptrs', INFOT, NOUT, LERR, OK )
281*
282* ZTPRFS
283*
284 SRNAMT = 'ztprfs'
285 INFOT = 1
286 CALL ZTPRFS( '/', 'n', 'n', 0, 0, a, b, 1, x, 1, r1, r2, w, rw,
287 $ info )
288 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
289 infot = 2
290 CALL ztprfs( 'u', '/', 'n', 0, 0, A, B, 1, X, 1, R1, R2, W, RW,
291 $ INFO )
292 CALL CHKXER( 'ztprfs', INFOT, NOUT, LERR, OK )
293 INFOT = 3
294 CALL ZTPRFS( 'u', 'n', '/', 0, 0, a, b, 1, x, 1, r1, r2, w, rw,
295 $ info )
296 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
297 infot = 4
298 CALL ztprfs( 'U', 'N', 'N', -1, 0, a, b, 1, x, 1, r1, r2, w,
299 $ rw, info )
300 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
301 infot = 5
302 CALL ztprfs( 'U', 'N', 'N', 0, -1, a, b, 1, x, 1, r1, r2, w,
303 $ rw, info )
304 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
305 infot = 8
306 CALL ztprfs( 'U', 'N', 'N', 2, 1, a, b, 1, x, 2, r1, r2, w, rw,
307 $ info )
308 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
309 infot = 10
310 CALL ztprfs( 'U', 'N', 'N', 2, 1, a, b, 2, x, 1, r1, r2, w, rw,
311 $ info )
312 CALL chkxer( 'ZTPRFS', infot, nout, lerr, ok )
313*
314* ZTPCON
315*
316 srnamt = 'ZTPCON'
317 infot = 1
318 CALL ztpcon( '/', 'U', 'N', 0, a, rcond, w, rw, info )
319 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
320 infot = 2
321 CALL ztpcon( '1', '/', 'N', 0, a, rcond, w, rw, info )
322 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
323 infot = 3
324 CALL ztpcon( '1', 'U', '/', 0, a, rcond, w, rw, info )
325 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
326 infot = 4
327 CALL ztpcon( '1', 'U', 'N', -1, a, rcond, w, rw, info )
328 CALL chkxer( 'ZTPCON', infot, nout, lerr, ok )
329*
330* ZLATPS
331*
332 srnamt = 'ZLATPS'
333 infot = 1
334 CALL zlatps( '/', 'N', 'N', 'N', 0, a, x, scale, rw, info )
335 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
336 infot = 2
337 CALL zlatps( 'U', '/', 'N', 'N', 0, a, x, scale, rw, info )
338 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
339 infot = 3
340 CALL zlatps( 'U', 'N', '/', 'N', 0, a, x, scale, rw, info )
341 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
342 infot = 4
343 CALL zlatps( 'U', 'N', 'N', '/', 0, a, x, scale, rw, info )
344 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
345 infot = 5
346 CALL zlatps( 'U', 'N', 'N', 'N', -1, a, x, scale, rw, info )
347 CALL chkxer( 'ZLATPS', infot, nout, lerr, ok )
348*
349* Test error exits for the banded triangular routines.
350*
351 ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
352*
353* ZTBTRS
354*
355 srnamt = 'ZTBTRS'
356 infot = 1
357 CALL ztbtrs( '/', 'N', 'N', 0, 0, 0, a, 1, x, 1, info )
358 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
359 infot = 2
360 CALL ztbtrs( 'U', '/', 'N', 0, 0, 0, a, 1, x, 1, info )
361 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
362 infot = 3
363 CALL ztbtrs( 'U', 'N', '/', 0, 0, 0, a, 1, x, 1, info )
364 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
365 infot = 4
366 CALL ztbtrs( 'U', 'N', 'N', -1, 0, 0, a, 1, x, 1, info )
367 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
368 infot = 5
369 CALL ztbtrs( 'U', 'N', 'N', 0, -1, 0, a, 1, x, 1, info )
370 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
371 infot = 6
372 CALL ztbtrs( 'U', 'N', 'N', 0, 0, -1, a, 1, x, 1, info )
373 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
374 infot = 8
375 CALL ztbtrs( 'U', 'N', 'N', 2, 1, 1, a, 1, x, 2, info )
376 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
377 infot = 10
378 CALL ztbtrs( 'U', 'N', 'N', 2, 0, 1, a, 1, x, 1, info )
379 CALL chkxer( 'ZTBTRS', infot, nout, lerr, ok )
380*
381* ZTBRFS
382*
383 srnamt = 'ZTBRFS'
384 infot = 1
385 CALL ztbrfs( '/', 'N', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
386 $ w, rw, info )
387 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
388 infot = 2
389 CALL ztbrfs( 'U', '/', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
390 $ w, rw, info )
391 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
392 infot = 3
393 CALL ztbrfs( 'U', 'N', '/', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
394 $ w, rw, info )
395 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
396 infot = 4
397 CALL ztbrfs( 'U', 'N', 'N', -1, 0, 0, a, 1, b, 1, x, 1, r1, r2,
398 $ w, rw, info )
399 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
400 infot = 5
401 CALL ztbrfs( 'U', 'N', 'N', 0, -1, 0, a, 1, b, 1, x, 1, r1, r2,
402 $ w, rw, info )
403 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
404 infot = 6
405 CALL ztbrfs( 'U', 'N', 'N', 0, 0, -1, a, 1, b, 1, x, 1, r1, r2,
406 $ w, rw, info )
407 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
408 infot = 8
409 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 1, b, 2, x, 2, r1, r2,
410 $ w, rw, info )
411 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
412 infot = 10
413 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 1, x, 2, r1, r2,
414 $ w, rw, info )
415 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
416 infot = 12
417 CALL ztbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 2, x, 1, r1, r2,
418 $ w, rw, info )
419 CALL chkxer( 'ZTBRFS', infot, nout, lerr, ok )
420*
421* ZTBCON
422*
423 srnamt = 'ZTBCON'
424 infot = 1
425 CALL ztbcon( '/', 'U', 'N', 0, 0, a, 1, rcond, w, rw, info )
426 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
427 infot = 2
428 CALL ztbcon( '1', '/', 'N', 0, 0, a, 1, rcond, w, rw, info )
429 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
430 infot = 3
431 CALL ztbcon( '1', 'U', '/', 0, 0, a, 1, rcond, w, rw, info )
432 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
433 infot = 4
434 CALL ztbcon( '1', 'U', 'N', -1, 0, a, 1, rcond, w, rw, info )
435 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
436 infot = 5
437 CALL ztbcon( '1', 'U', 'N', 0, -1, a, 1, rcond, w, rw, info )
438 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
439 infot = 7
440 CALL ztbcon( '1', 'U', 'N', 2, 1, a, 1, rcond, w, rw, info )
441 CALL chkxer( 'ZTBCON', infot, nout, lerr, ok )
442*
443* ZLATBS
444*
445 srnamt = 'ZLATBS'
446 infot = 1
447 CALL zlatbs( '/', 'N', 'N', 'N', 0, 0, a, 1, x, scale, rw,
448 $ info )
449 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
450 infot = 2
451 CALL zlatbs( 'U', '/', 'N', 'N', 0, 0, a, 1, x, scale, rw,
452 $ info )
453 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
454 infot = 3
455 CALL zlatbs( 'U', 'N', '/', 'N', 0, 0, a, 1, x, scale, rw,
456 $ info )
457 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
458 infot = 4
459 CALL zlatbs( 'U', 'N', 'N', '/', 0, 0, a, 1, x, scale, rw,
460 $ info )
461 CALL chkxer( 'ZLATBS', infot, nout, lerr, ok )
462 infot = 5
463 CALL zlatbs( 'U', 'n', 'n', 'n', -1, 0, A, 1, X, SCALE, RW,
464 $ INFO )
465 CALL CHKXER( 'zlatbs', INFOT, NOUT, LERR, OK )
466 INFOT = 6
467 CALL ZLATBS( 'u', 'n', 'n', 'n', 1, -1, A, 1, X, SCALE, RW,
468 $ INFO )
469 CALL CHKXER( 'zlatbs', INFOT, NOUT, LERR, OK )
470 INFOT = 8
471 CALL ZLATBS( 'u', 'n', 'n', 'n', 2, 1, A, 1, X, SCALE, RW,
472 $ INFO )
473 CALL CHKXER( 'zlatbs', INFOT, NOUT, LERR, OK )
474 END IF
475*
476* Print a summary line.
477*
478 CALL ALAESM( PATH, OK, NOUT )
479*
480 RETURN
481*
482* End of ZERRTR
483*
484 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
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 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 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 ztrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)
ZTRCON
Definition ztrcon.f:137
subroutine ztbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)
ZTBTRS
Definition ztbtrs.f:146
subroutine ztprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZTPRFS
Definition ztprfs.f:174
subroutine ztrtri(uplo, diag, n, a, lda, info)
ZTRTRI
Definition ztrtri.f:109
subroutine ztptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)
ZTPTRS
Definition ztptrs.f:130
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 ztptri(uplo, diag, n, ap, info)
ZTPTRI
Definition ztptri.f:117
subroutine ztrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
ZTRTRS
Definition ztrtrs.f:140
subroutine ztpcon(norm, uplo, diag, n, ap, rcond, work, rwork, info)
ZTPCON
Definition ztpcon.f:130
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 zerrtr(path, nunit)
ZERRTR
Definition zerrtr.f:54