LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
derrtr.f
Go to the documentation of this file.
1*> \brief \b DERRTR
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 DERRTR( 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*> DERRTR tests the error exits for the DOUBLE PRECISION triangular
25*> routines.
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 double_lin
52*
53* =====================================================================
54 SUBROUTINE derrtr( 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 = 2 )
70* ..
71* .. Local Scalars ..
72 CHARACTER*2 C2
73 INTEGER INFO
74 DOUBLE PRECISION RCOND, SCALE, SCALES(0)
75* ..
76* .. Local Arrays ..
77 INTEGER IW( NMAX )
78 DOUBLE PRECISION A( NMAX, NMAX ), B( NMAX ), R1( NMAX ),
79 $ R2( NMAX ), W( NMAX ), X( NMAX )
80* ..
81* .. External Functions ..
82 LOGICAL LSAMEN
83 EXTERNAL lsamen
84* ..
85* .. External Subroutines ..
86 EXTERNAL alaesm, chkxer, dlatbs, dlatps, dlatrs,
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* .. Executable Statements ..
101*
102 nout = nunit
103 WRITE( nout, fmt = * )
104 c2 = path( 2: 3 )
105 a( 1, 1 ) = 1.d0
106 a( 1, 2 ) = 2.d0
107 a( 2, 2 ) = 3.d0
108 a( 2, 1 ) = 4.d0
109 ok = .true.
110*
111 IF( lsamen( 2, c2, 'TR' ) ) THEN
112*
113* Test error exits for the general triangular routines.
114*
115* DTRTRI
116*
117 srnamt = 'DTRTRI'
118 infot = 1
119 CALL dtrtri( '/', 'N', 0, a, 1, info )
120 CALL chkxer( 'DTRTRI', infot, nout, lerr, ok )
121 infot = 2
122 CALL dtrtri( 'U', '/', 0, a, 1, info )
123 CALL chkxer( 'DTRTRI', infot, nout, lerr, ok )
124 infot = 3
125 CALL dtrtri( 'U', 'N', -1, a, 1, info )
126 CALL chkxer( 'DTRTRI', infot, nout, lerr, ok )
127 infot = 5
128 CALL dtrtri( 'U', 'N', 2, a, 1, info )
129 CALL chkxer( 'DTRTRI', infot, nout, lerr, ok )
130*
131* DTRTI2
132*
133 srnamt = 'DTRTI2'
134 infot = 1
135 CALL dtrti2( '/', 'N', 0, a, 1, info )
136 CALL chkxer( 'DTRTI2', infot, nout, lerr, ok )
137 infot = 2
138 CALL dtrti2( 'U', '/', 0, a, 1, info )
139 CALL chkxer( 'DTRTI2', infot, nout, lerr, ok )
140 infot = 3
141 CALL dtrti2( 'U', 'N', -1, a, 1, info )
142 CALL chkxer( 'DTRTI2', infot, nout, lerr, ok )
143 infot = 5
144 CALL dtrti2( 'U', 'N', 2, a, 1, info )
145 CALL chkxer( 'DTRTI2', infot, nout, lerr, ok )
146*
147* DTRTRS
148*
149 srnamt = 'DTRTRS'
150 infot = 1
151 CALL dtrtrs( '/', 'N', 'N', 0, 0, a, 1, x, 1, info )
152 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
153 infot = 2
154 CALL dtrtrs( 'U', '/', 'N', 0, 0, a, 1, x, 1, info )
155 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
156 infot = 3
157 CALL dtrtrs( 'U', 'N', '/', 0, 0, a, 1, x, 1, info )
158 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
159 infot = 4
160 CALL dtrtrs( 'U', 'N', 'N', -1, 0, a, 1, x, 1, info )
161 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
162 infot = 5
163 CALL dtrtrs( 'U', 'N', 'N', 0, -1, a, 1, x, 1, info )
164 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
165 infot = 7
166 CALL dtrtrs( 'U', 'N', 'N', 2, 1, a, 1, x, 2, info )
167 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
168 infot = 9
169 CALL dtrtrs( 'U', 'N', 'N', 2, 1, a, 2, x, 1, info )
170 CALL chkxer( 'DTRTRS', infot, nout, lerr, ok )
171*
172* DTRRFS
173*
174 srnamt = 'DTRRFS'
175 infot = 1
176 CALL dtrrfs( '/', 'N', 'N', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
177 $ iw, info )
178 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
179 infot = 2
180 CALL dtrrfs( 'U', '/', 'N', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
181 $ iw, info )
182 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
183 infot = 3
184 CALL dtrrfs( 'U', 'N', '/', 0, 0, a, 1, b, 1, x, 1, r1, r2, w,
185 $ iw, info )
186 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
187 infot = 4
188 CALL dtrrfs( 'U', 'N', 'N', -1, 0, a, 1, b, 1, x, 1, r1, r2, w,
189 $ iw, info )
190 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
191 infot = 5
192 CALL dtrrfs( 'U', 'N', 'N', 0, -1, a, 1, b, 1, x, 1, r1, r2, w,
193 $ iw, info )
194 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
195 infot = 7
196 CALL dtrrfs( 'U', 'N', 'N', 2, 1, a, 1, b, 2, x, 2, r1, r2, w,
197 $ iw, info )
198 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
199 infot = 9
200 CALL dtrrfs( 'U', 'N', 'N', 2, 1, a, 2, b, 1, x, 2, r1, r2, w,
201 $ iw, info )
202 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
203 infot = 11
204 CALL dtrrfs( 'U', 'N', 'N', 2, 1, a, 2, b, 2, x, 1, r1, r2, w,
205 $ iw, info )
206 CALL chkxer( 'DTRRFS', infot, nout, lerr, ok )
207*
208* DTRCON
209*
210 srnamt = 'DTRCON'
211 infot = 1
212 CALL dtrcon( '/', 'U', 'N', 0, a, 1, rcond, w, iw, info )
213 CALL chkxer( 'DTRCON', infot, nout, lerr, ok )
214 infot = 2
215 CALL dtrcon( '1', '/', 'N', 0, a, 1, rcond, w, iw, info )
216 CALL chkxer( 'DTRCON', infot, nout, lerr, ok )
217 infot = 3
218 CALL dtrcon( '1', 'U', '/', 0, a, 1, rcond, w, iw, info )
219 CALL chkxer( 'DTRCON', infot, nout, lerr, ok )
220 infot = 4
221 CALL dtrcon( '1', 'U', 'N', -1, a, 1, rcond, w, iw, info )
222 CALL chkxer( 'DTRCON', infot, nout, lerr, ok )
223 infot = 6
224 CALL dtrcon( '1', 'U', 'N', 2, a, 1, rcond, w, iw, info )
225 CALL chkxer( 'DTRCON', infot, nout, lerr, ok )
226*
227* DLATRS
228*
229 srnamt = 'DLATRS'
230 infot = 1
231 CALL dlatrs( '/', 'N', 'N', 'N', 0, a, 1, x, scale, w, info )
232 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
233 infot = 2
234 CALL dlatrs( 'U', '/', 'N', 'N', 0, a, 1, x, scale, w, info )
235 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
236 infot = 3
237 CALL dlatrs( 'U', 'N', '/', 'N', 0, a, 1, x, scale, w, info )
238 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
239 infot = 4
240 CALL dlatrs( 'U', 'N', 'N', '/', 0, a, 1, x, scale, w, info )
241 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
242 infot = 5
243 CALL dlatrs( 'U', 'N', 'N', 'N', -1, a, 1, x, scale, w, info )
244 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
245 infot = 7
246 CALL dlatrs( 'U', 'N', 'N', 'N', 2, a, 1, x, scale, w, info )
247 CALL chkxer( 'DLATRS', infot, nout, lerr, ok )
248*
249* DLATRS3
250*
251 srnamt = 'DLATRS3'
252 infot = 1
253 CALL dlatrs3( '/', 'N', 'N', 'N', 0, 0, a, 1, x, 1, scales,
254 $ w, w( 2 ), 1, info )
255 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
256 infot = 2
257 CALL dlatrs3( 'U', '/', 'N', 'N', 0, 0, a, 1, x, 1, scales,
258 $ w, w( 2 ), 1, info )
259 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
260 infot = 3
261 CALL dlatrs3( 'U', 'N', '/', 'N', 0, 0, a, 1, x, 1, scales,
262 $ w, w( 2 ), 1, info )
263 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
264 infot = 4
265 CALL dlatrs3( 'U', 'N', 'N', '/', 0, 0, a, 1, x, 1, scales,
266 $ w, w( 2 ), 1, info )
267 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
268 infot = 5
269 CALL dlatrs3( 'U', 'N', 'N', 'N', -1, 0, a, 1, x, 1, scales,
270 $ w, w( 2 ), 1, info )
271 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
272 infot = 6
273 CALL dlatrs3( 'U', 'N', 'N', 'N', 0, -1, a, 1, x, 1, scales,
274 $ w, w( 2 ), 1, info )
275 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
276 infot = 8
277 CALL dlatrs3( 'U', 'N', 'N', 'N', 2, 0, a, 1, x, 1, scales,
278 $ w, w( 2 ), 1, info )
279 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
280 infot = 10
281 CALL dlatrs3( 'U', 'N', 'N', 'N', 2, 0, a, 2, x, 1, scales,
282 $ w, w( 2 ), 1, info )
283 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
284 infot = 14
285 CALL dlatrs3( 'U', 'N', 'N', 'N', 1, 0, a, 1, x, 1, scales,
286 $ w, w( 2 ), 0, info )
287 CALL chkxer( 'DLATRS3', infot, nout, lerr, ok )
288*
289 ELSE IF( lsamen( 2, c2, 'TP' ) ) THEN
290*
291* Test error exits for the packed triangular routines.
292*
293* DTPTRI
294*
295 srnamt = 'DTPTRI'
296 infot = 1
297 CALL dtptri( '/', 'N', 0, a, info )
298 CALL chkxer( 'DTPTRI', infot, nout, lerr, ok )
299 infot = 2
300 CALL dtptri( 'U', '/', 0, a, info )
301 CALL chkxer( 'DTPTRI', infot, nout, lerr, ok )
302 infot = 3
303 CALL dtptri( 'U', 'N', -1, a, info )
304 CALL chkxer( 'DTPTRI', infot, nout, lerr, ok )
305*
306* DTPTRS
307*
308 srnamt = 'DTPTRS'
309 infot = 1
310 CALL dtptrs( '/', 'N', 'N', 0, 0, a, x, 1, info )
311 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
312 infot = 2
313 CALL dtptrs( 'U', '/', 'N', 0, 0, a, x, 1, info )
314 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
315 infot = 3
316 CALL dtptrs( 'U', 'N', '/', 0, 0, a, x, 1, info )
317 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
318 infot = 4
319 CALL dtptrs( 'U', 'N', 'N', -1, 0, a, x, 1, info )
320 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
321 infot = 5
322 CALL dtptrs( 'U', 'N', 'N', 0, -1, a, x, 1, info )
323 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
324 infot = 8
325 CALL dtptrs( 'U', 'N', 'N', 2, 1, a, x, 1, info )
326 CALL chkxer( 'DTPTRS', infot, nout, lerr, ok )
327*
328* DTPRFS
329*
330 srnamt = 'DTPRFS'
331 infot = 1
332 CALL dtprfs( '/', 'N', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
333 $ info )
334 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
335 infot = 2
336 CALL dtprfs( 'U', '/', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
337 $ info )
338 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
339 infot = 3
340 CALL dtprfs( 'U', 'N', '/', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
341 $ info )
342 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
343 infot = 4
344 CALL dtprfs( 'U', 'N', 'N', -1, 0, a, b, 1, x, 1, r1, r2, w,
345 $ iw, info )
346 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
347 infot = 5
348 CALL dtprfs( 'U', 'N', 'N', 0, -1, a, b, 1, x, 1, r1, r2, w,
349 $ iw, info )
350 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
351 infot = 8
352 CALL dtprfs( 'U', 'N', 'N', 2, 1, a, b, 1, x, 2, r1, r2, w, iw,
353 $ info )
354 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
355 infot = 10
356 CALL dtprfs( 'U', 'N', 'N', 2, 1, a, b, 2, x, 1, r1, r2, w, iw,
357 $ info )
358 CALL chkxer( 'DTPRFS', infot, nout, lerr, ok )
359*
360* DTPCON
361*
362 srnamt = 'DTPCON'
363 infot = 1
364 CALL dtpcon( '/', 'U', 'N', 0, a, rcond, w, iw, info )
365 CALL chkxer( 'DTPCON', infot, nout, lerr, ok )
366 infot = 2
367 CALL dtpcon( '1', '/', 'N', 0, a, rcond, w, iw, info )
368 CALL chkxer( 'DTPCON', infot, nout, lerr, ok )
369 infot = 3
370 CALL dtpcon( '1', 'U', '/', 0, a, rcond, w, iw, info )
371 CALL chkxer( 'DTPCON', infot, nout, lerr, ok )
372 infot = 4
373 CALL dtpcon( '1', 'U', 'N', -1, a, rcond, w, iw, info )
374 CALL chkxer( 'DTPCON', infot, nout, lerr, ok )
375*
376* DLATPS
377*
378 srnamt = 'DLATPS'
379 infot = 1
380 CALL dlatps( '/', 'N', 'N', 'N', 0, a, x, scale, w, info )
381 CALL chkxer( 'DLATPS', infot, nout, lerr, ok )
382 infot = 2
383 CALL dlatps( 'U', '/', 'N', 'N', 0, a, x, scale, w, info )
384 CALL chkxer( 'DLATPS', infot, nout, lerr, ok )
385 infot = 3
386 CALL dlatps( 'U', 'N', '/', 'N', 0, a, x, scale, w, info )
387 CALL chkxer( 'DLATPS', infot, nout, lerr, ok )
388 infot = 4
389 CALL dlatps( 'U', 'N', 'N', '/', 0, a, x, scale, w, info )
390 CALL chkxer( 'DLATPS', infot, nout, lerr, ok )
391 infot = 5
392 CALL dlatps( 'U', 'N', 'N', 'N', -1, a, x, scale, w, info )
393 CALL chkxer( 'DLATPS', infot, nout, lerr, ok )
394*
395 ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
396*
397* Test error exits for the banded triangular routines.
398*
399* DTBTRS
400*
401 srnamt = 'DTBTRS'
402 infot = 1
403 CALL dtbtrs( '/', 'N', 'N', 0, 0, 0, a, 1, x, 1, info )
404 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
405 infot = 2
406 CALL dtbtrs( 'U', '/', 'N', 0, 0, 0, a, 1, x, 1, info )
407 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
408 infot = 3
409 CALL dtbtrs( 'U', 'N', '/', 0, 0, 0, a, 1, x, 1, info )
410 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
411 infot = 4
412 CALL dtbtrs( 'U', 'N', 'N', -1, 0, 0, a, 1, x, 1, info )
413 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
414 infot = 5
415 CALL dtbtrs( 'U', 'N', 'N', 0, -1, 0, a, 1, x, 1, info )
416 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
417 infot = 6
418 CALL dtbtrs( 'U', 'N', 'N', 0, 0, -1, a, 1, x, 1, info )
419 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
420 infot = 8
421 CALL dtbtrs( 'U', 'N', 'N', 2, 1, 1, a, 1, x, 2, info )
422 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
423 infot = 10
424 CALL dtbtrs( 'U', 'N', 'N', 2, 0, 1, a, 1, x, 1, info )
425 CALL chkxer( 'DTBTRS', infot, nout, lerr, ok )
426*
427* DTBRFS
428*
429 srnamt = 'DTBRFS'
430 infot = 1
431 CALL dtbrfs( '/', 'N', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
432 $ w, iw, info )
433 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
434 infot = 2
435 CALL dtbrfs( 'U', '/', 'N', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
436 $ w, iw, info )
437 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
438 infot = 3
439 CALL dtbrfs( 'U', 'N', '/', 0, 0, 0, a, 1, b, 1, x, 1, r1, r2,
440 $ w, iw, info )
441 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
442 infot = 4
443 CALL dtbrfs( 'U', 'N', 'N', -1, 0, 0, a, 1, b, 1, x, 1, r1, r2,
444 $ w, iw, info )
445 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
446 infot = 5
447 CALL dtbrfs( 'U', 'N', 'N', 0, -1, 0, a, 1, b, 1, x, 1, r1, r2,
448 $ w, iw, info )
449 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
450 infot = 6
451 CALL dtbrfs( 'U', 'N', 'N', 0, 0, -1, a, 1, b, 1, x, 1, r1, r2,
452 $ w, iw, info )
453 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
454 infot = 8
455 CALL dtbrfs( 'U', 'N', 'N', 2, 1, 1, a, 1, b, 2, x, 2, r1, r2,
456 $ w, iw, info )
457 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
458 infot = 10
459 CALL dtbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 1, x, 2, r1, r2,
460 $ w, iw, info )
461 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
462 infot = 12
463 CALL dtbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 2, x, 1, r1, r2,
464 $ w, iw, info )
465 CALL chkxer( 'DTBRFS', infot, nout, lerr, ok )
466*
467* DTBCON
468*
469 srnamt = 'DTBCON'
470 infot = 1
471 CALL dtbcon( '/', 'U', 'N', 0, 0, a, 1, rcond, w, iw, info )
472 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
473 infot = 2
474 CALL dtbcon( '1', '/', 'N', 0, 0, a, 1, rcond, w, iw, info )
475 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
476 infot = 3
477 CALL dtbcon( '1', 'U', '/', 0, 0, a, 1, rcond, w, iw, info )
478 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
479 infot = 4
480 CALL dtbcon( '1', 'U', 'N', -1, 0, a, 1, rcond, w, iw, info )
481 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
482 infot = 5
483 CALL dtbcon( '1', 'U', 'N', 0, -1, a, 1, rcond, w, iw, info )
484 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
485 infot = 7
486 CALL dtbcon( '1', 'U', 'N', 2, 1, a, 1, rcond, w, iw, info )
487 CALL chkxer( 'DTBCON', infot, nout, lerr, ok )
488*
489* DLATBS
490*
491 srnamt = 'DLATBS'
492 infot = 1
493 CALL dlatbs( '/', 'N', 'N', 'N', 0, 0, a, 1, x, scale, w,
494 $ info )
495 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
496 infot = 2
497 CALL dlatbs( 'U', '/', 'N', 'N', 0, 0, a, 1, x, scale, w,
498 $ info )
499 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
500 infot = 3
501 CALL dlatbs( 'U', 'N', '/', 'N', 0, 0, a, 1, x, scale, w,
502 $ info )
503 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
504 infot = 4
505 CALL dlatbs( 'U', 'N', 'N', '/', 0, 0, a, 1, x, scale, w,
506 $ info )
507 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
508 infot = 5
509 CALL dlatbs( 'U', 'N', 'N', 'N', -1, 0, a, 1, x, scale, w,
510 $ info )
511 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
512 infot = 6
513 CALL dlatbs( 'U', 'N', 'N', 'N', 1, -1, a, 1, x, scale, w,
514 $ info )
515 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
516 infot = 8
517 CALL dlatbs( 'U', 'N', 'N', 'N', 2, 1, a, 1, x, scale, w,
518 $ info )
519 CALL chkxer( 'DLATBS', infot, nout, lerr, ok )
520 END IF
521*
522* Print a summary line.
523*
524 CALL alaesm( path, ok, nout )
525*
526 RETURN
527*
528* End of DERRTR
529*
530 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine derrtr(path, nunit)
DERRTR
Definition derrtr.f:55
subroutine dlatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)
DLATBS solves a triangular banded system of equations.
Definition dlatbs.f:242
subroutine dlatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
DLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition dlatps.f:229
subroutine dlatrs3(uplo, trans, diag, normin, n, nrhs, a, lda, x, ldx, scale, cnorm, work, lwork, info)
DLATRS3 solves a triangular system of equations with the scale factors set to prevent overflow.
Definition dlatrs3.f:229
subroutine dlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
DLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition dlatrs.f:238
subroutine dtbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, iwork, info)
DTBCON
Definition dtbcon.f:143
subroutine dtbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DTBRFS
Definition dtbrfs.f:188
subroutine dtbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)
DTBTRS
Definition dtbtrs.f:146
subroutine dtpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)
DTPCON
Definition dtpcon.f:130
subroutine dtprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DTPRFS
Definition dtprfs.f:175
subroutine dtptri(uplo, diag, n, ap, info)
DTPTRI
Definition dtptri.f:117
subroutine dtptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)
DTPTRS
Definition dtptrs.f:130
subroutine dtrcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)
DTRCON
Definition dtrcon.f:137
subroutine dtrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DTRRFS
Definition dtrrfs.f:182
subroutine dtrti2(uplo, diag, n, a, lda, info)
DTRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
Definition dtrti2.f:110
subroutine dtrtri(uplo, diag, n, a, lda, info)
DTRTRI
Definition dtrtri.f:109
subroutine dtrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
DTRTRS
Definition dtrtrs.f:140