OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
serrtr.f
Go to the documentation of this file.
1*> \brief \b SERRTR
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 SERRTR( 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*> SERRTR tests the error exits for the REAL 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 single_lin
52*
53* =====================================================================
54 SUBROUTINE serrtr( 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 REAL RCOND, SCALE
75* ..
76* .. Local Arrays ..
77 INTEGER IW( NMAX )
78 REAL 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, slatbs, slatps, slatrs, stbcon,
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.
105 a( 1, 2 ) = 2.
106 a( 2, 2 ) = 3.
107 a( 2, 1 ) = 4.
108 ok = .true.
109*
110 IF( lsamen( 2, c2, 'TR' ) ) THEN
111*
112* Test error exits for the general triangular routines.
113*
114* STRTRI
115*
116 srnamt = 'STRTRI'
117 infot = 1
118 CALL strtri( '/', 'N', 0, a, 1, info )
119 CALL chkxer( 'STRTRI', infot, nout, lerr, ok )
120 infot = 2
121 CALL strtri( 'U', '/', 0, a, 1, info )
122 CALL chkxer( 'STRTRI', infot, nout, lerr, ok )
123 infot = 3
124 CALL strtri( 'U', 'N', -1, a, 1, info )
125 CALL chkxer( 'STRTRI', infot, nout, lerr, ok )
126 infot = 5
127 CALL strtri( 'U', 'N', 2, a, 1, info )
128 CALL chkxer( 'STRTRI', infot, nout, lerr, ok )
129*
130* STRTI2
131*
132 srnamt = 'STRTI2'
133 infot = 1
134 CALL strti2( '/', 'N', 0, a, 1, info )
135 CALL chkxer( 'STRTI2', infot, nout, lerr, ok )
136 infot = 2
137 CALL strti2( 'U', '/', 0, a, 1, info )
138 CALL chkxer( 'STRTI2', infot, nout, lerr, ok )
139 infot = 3
140 CALL strti2( 'U', 'N', -1, a, 1, info )
141 CALL chkxer( 'STRTI2', infot, nout, lerr, ok )
142 infot = 5
143 CALL strti2( 'U', 'N', 2, a, 1, info )
144 CALL chkxer( 'STRTI2', infot, nout, lerr, ok )
145*
146* STRTRS
147*
148 srnamt = 'STRTRS'
149 infot = 1
150 CALL strtrs( '/', 'N', 'N', 0, 0, a, 1, x, 1, info )
151 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
152 infot = 2
153 CALL strtrs( 'U', '/', 'N', 0, 0, a, 1, x, 1, info )
154 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
155 infot = 3
156 CALL strtrs( 'U', 'N', '/', 0, 0, a, 1, x, 1, info )
157 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
158 infot = 4
159 CALL strtrs( 'U', 'n', 'n', -1, 0, A, 1, X, 1, INFO )
160 CALL CHKXER( 'strtrs', INFOT, NOUT, LERR, OK )
161 INFOT = 5
162 CALL STRTRS( 'u', 'n', 'n', 0, -1, a, 1, x, 1, info )
163 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
164 infot = 7
165 CALL strtrs( 'U', 'N', 'N', 2, 1, a, 1, x, 2, info )
166 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
167 infot = 9
168 CALL strtrs( 'U', 'N', 'N', 2, 1, a, 2, x, 1, info )
169 CALL chkxer( 'STRTRS', infot, nout, lerr, ok )
170*
171* STRRFS
172*
173 srnamt = 'strrfs'
174 INFOT = 1
175 CALL STRRFS( '/', 'n', 'n', 0, 0, A, 1, B, 1, X, 1, R1, R2, W,
176 $ IW, INFO )
177 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
178 INFOT = 2
179 CALL STRRFS( 'u', '/', 'n', 0, 0, A, 1, B, 1, X, 1, R1, R2, W,
180 $ IW, INFO )
181 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
182 INFOT = 3
183 CALL STRRFS( 'u', 'n', '/', 0, 0, A, 1, B, 1, X, 1, R1, R2, W,
184 $ IW, INFO )
185 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
186 INFOT = 4
187 CALL STRRFS( 'u', 'n', 'n', -1, 0, A, 1, B, 1, X, 1, R1, R2, W,
188 $ IW, INFO )
189 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
190 INFOT = 5
191 CALL STRRFS( 'u', 'n', 'n', 0, -1, A, 1, B, 1, X, 1, R1, R2, W,
192 $ IW, INFO )
193 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
194 INFOT = 7
195 CALL STRRFS( 'u', 'n', 'n', 2, 1, A, 1, B, 2, X, 2, R1, R2, W,
196 $ IW, INFO )
197 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
198 INFOT = 9
199 CALL STRRFS( 'u', 'n', 'n', 2, 1, A, 2, B, 1, X, 2, R1, R2, W,
200 $ IW, INFO )
201 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
202 INFOT = 11
203 CALL STRRFS( 'u', 'n', 'n', 2, 1, A, 2, B, 2, X, 1, R1, R2, W,
204 $ IW, INFO )
205 CALL CHKXER( 'strrfs', INFOT, NOUT, LERR, OK )
206*
207* STRCON
208*
209 SRNAMT = 'strcon'
210 INFOT = 1
211 CALL STRCON( '/', 'u', 'n', 0, A, 1, RCOND, W, IW, INFO )
212 CALL CHKXER( 'strcon', INFOT, NOUT, LERR, OK )
213 INFOT = 2
214 CALL STRCON( '1', '/', 'n', 0, A, 1, RCOND, W, IW, INFO )
215 CALL CHKXER( 'strcon', INFOT, NOUT, LERR, OK )
216 INFOT = 3
217 CALL STRCON( '1', 'u', '/', 0, A, 1, RCOND, W, IW, INFO )
218 CALL CHKXER( 'strcon', INFOT, NOUT, LERR, OK )
219 INFOT = 4
220 CALL STRCON( '1', 'u', 'n', -1, A, 1, RCOND, W, IW, INFO )
221 CALL CHKXER( 'strcon', INFOT, NOUT, LERR, OK )
222 INFOT = 6
223 CALL STRCON( '1', 'u', 'n', 2, A, 1, RCOND, W, IW, INFO )
224 CALL CHKXER( 'strcon', INFOT, NOUT, LERR, OK )
225*
226* SLATRS
227*
228 SRNAMT = 'slatrs'
229 INFOT = 1
230 CALL SLATRS( '/', 'n', 'n', 'n', 0, A, 1, X, SCALE, W, INFO )
231 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
232 INFOT = 2
233 CALL SLATRS( 'u', '/', 'n', 'n', 0, A, 1, X, SCALE, W, INFO )
234 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
235 INFOT = 3
236 CALL SLATRS( 'u', 'n', '/', 'n', 0, A, 1, X, SCALE, W, INFO )
237 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
238 INFOT = 4
239 CALL SLATRS( 'u', 'n', 'n', '/', 0, A, 1, X, SCALE, W, INFO )
240 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
241 INFOT = 5
242 CALL SLATRS( 'u', 'n', 'n', 'n', -1, A, 1, X, SCALE, W, INFO )
243 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
244 INFOT = 7
245 CALL SLATRS( 'u', 'n', 'n', 'n', 2, A, 1, X, SCALE, W, INFO )
246 CALL CHKXER( 'slatrs', INFOT, NOUT, LERR, OK )
247*
248 ELSE IF( LSAMEN( 2, C2, 'tp' ) ) THEN
249*
250* Test error exits for the packed triangular routines.
251*
252* STPTRI
253*
254 SRNAMT = 'stptri'
255 INFOT = 1
256 CALL STPTRI( '/', 'n', 0, A, INFO )
257 CALL CHKXER( 'stptri', INFOT, NOUT, LERR, OK )
258 INFOT = 2
259 CALL STPTRI( 'u', '/', 0, A, INFO )
260 CALL CHKXER( 'stptri', INFOT, NOUT, LERR, OK )
261 INFOT = 3
262 CALL STPTRI( 'u', 'n', -1, A, INFO )
263 CALL CHKXER( 'stptri', INFOT, NOUT, LERR, OK )
264*
265* STPTRS
266*
267 SRNAMT = 'stptrs'
268 INFOT = 1
269 CALL STPTRS( '/', 'n', 'n', 0, 0, A, X, 1, INFO )
270 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
271 INFOT = 2
272 CALL STPTRS( 'u', '/', 'n', 0, 0, A, X, 1, INFO )
273 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
274 INFOT = 3
275 CALL STPTRS( 'u', 'n', '/', 0, 0, A, X, 1, INFO )
276 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
277 INFOT = 4
278 CALL STPTRS( 'u', 'n', 'n', -1, 0, A, X, 1, INFO )
279 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
280 INFOT = 5
281 CALL STPTRS( 'u', 'n', 'n', 0, -1, A, X, 1, INFO )
282 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
283 INFOT = 8
284 CALL STPTRS( 'u', 'n', 'n', 2, 1, A, X, 1, INFO )
285 CALL CHKXER( 'stptrs', INFOT, NOUT, LERR, OK )
286*
287* STPRFS
288*
289 SRNAMT = 'stprfs'
290 infot = 1
291 CALL stprfs( '/', 'N', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
292 $ info )
293 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
294 infot = 2
295 CALL stprfs( 'U', '/', 'N', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
296 $ info )
297 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
298 infot = 3
299 CALL stprfs( 'U', 'N', '/', 0, 0, a, b, 1, x, 1, r1, r2, w, iw,
300 $ info )
301 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
302 infot = 4
303 CALL stprfs( 'U', 'N', 'N', -1, 0, a, b, 1, x, 1, r1, r2, w,
304 $ iw, info )
305 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
306 infot = 5
307 CALL stprfs( 'U', 'N', 'N', 0, -1, a, b, 1, x, 1, r1, r2, w,
308 $ iw, info )
309 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
310 infot = 8
311 CALL stprfs( 'U', 'N', 'N', 2, 1, a, b, 1, x, 2, r1, r2, w, iw,
312 $ info )
313 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
314 infot = 10
315 CALL stprfs( 'U', 'N', 'N', 2, 1, a, b, 2, x, 1, r1, r2, w, iw,
316 $ info )
317 CALL chkxer( 'STPRFS', infot, nout, lerr, ok )
318*
319* STPCON
320*
321 srnamt = 'STPCON'
322 infot = 1
323 CALL stpcon( '/', 'U', 'N', 0, a, rcond, w, iw, info )
324 CALL chkxer( 'STPCON', infot, nout, lerr, ok )
325 infot = 2
326 CALL stpcon( '1', '/', 'N', 0, a, rcond, w, iw, info )
327 CALL chkxer( 'STPCON', infot, nout, lerr, ok )
328 infot = 3
329 CALL stpcon( '1', 'U', '/', 0, a, rcond, w, iw, info )
330 CALL chkxer( 'STPCON', infot, nout, lerr, ok )
331 infot = 4
332 CALL stpcon( '1', 'U', 'N', -1, a, rcond, w, iw, info )
333 CALL chkxer( 'STPCON', infot, nout, lerr, ok )
334*
335* SLATPS
336*
337 srnamt = 'SLATPS'
338 infot = 1
339 CALL slatps( '/', 'N', 'N', 'N', 0, a, x, scale, w, info )
340 CALL chkxer( 'SLATPS', infot, nout, lerr, ok )
341 infot = 2
342 CALL slatps( 'U', '/', 'N', 'N', 0, a, x, scale, w, info )
343 CALL chkxer( 'SLATPS', infot, nout, lerr, ok )
344 infot = 3
345 CALL slatps( 'U', 'N', '/', 'N', 0, a, x, scale, w, info )
346 CALL chkxer( 'SLATPS', infot, nout, lerr, ok )
347 infot = 4
348 CALL slatps( 'U', 'N', 'N', '/', 0, a, x, scale, w, info )
349 CALL chkxer( 'SLATPS', infot, nout, lerr, ok )
350 infot = 5
351 CALL slatps( 'U', 'N', 'N', 'N', -1, a, x, scale, w, info )
352 CALL chkxer( 'SLATPS', infot, nout, lerr, ok )
353*
354 ELSE IF( lsamen( 2, c2, 'TB' ) ) THEN
355*
356* Test error exits for the banded triangular routines.
357*
358* STBTRS
359*
360 srnamt = 'stbtrs'
361 INFOT = 1
362 CALL STBTRS( '/', 'n', 'n', 0, 0, 0, A, 1, X, 1, INFO )
363 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
364 INFOT = 2
365 CALL STBTRS( 'u', '/', 'n', 0, 0, 0, A, 1, X, 1, INFO )
366 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
367 INFOT = 3
368 CALL STBTRS( 'u', 'n', '/', 0, 0, 0, A, 1, X, 1, INFO )
369 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
370 INFOT = 4
371 CALL STBTRS( 'u', 'n', 'n', -1, 0, 0, A, 1, X, 1, INFO )
372 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
373 INFOT = 5
374 CALL STBTRS( 'u', 'n', 'n', 0, -1, 0, A, 1, X, 1, INFO )
375 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
376 INFOT = 6
377 CALL STBTRS( 'u', 'n', 'n', 0, 0, -1, A, 1, X, 1, INFO )
378 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
379 INFOT = 8
380 CALL STBTRS( 'u', 'n', 'n', 2, 1, 1, A, 1, X, 2, INFO )
381 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
382 INFOT = 10
383 CALL STBTRS( 'u', 'n', 'n', 2, 0, 1, A, 1, X, 1, INFO )
384 CALL CHKXER( 'stbtrs', INFOT, NOUT, LERR, OK )
385*
386* STBRFS
387*
388 SRNAMT = 'stbrfs'
389 INFOT = 1
390 CALL STBRFS( '/', 'n', 'n', 0, 0, 0, A, 1, B, 1, X, 1, R1, R2,
391 $ W, IW, INFO )
392 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
393 INFOT = 2
394 CALL STBRFS( 'u', '/', 'n', 0, 0, 0, A, 1, B, 1, X, 1, R1, R2,
395 $ W, IW, INFO )
396 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
397 INFOT = 3
398 CALL STBRFS( 'u', 'n', '/', 0, 0, 0, A, 1, B, 1, X, 1, R1, R2,
399 $ W, IW, INFO )
400 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
401 INFOT = 4
402 CALL STBRFS( 'u', 'n', 'n', -1, 0, 0, A, 1, B, 1, X, 1, R1, R2,
403 $ W, IW, INFO )
404 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
405 INFOT = 5
406 CALL STBRFS( 'u', 'n', 'n', 0, -1, 0, A, 1, B, 1, X, 1, R1, R2,
407 $ W, IW, INFO )
408 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
409 INFOT = 6
410 CALL STBRFS( 'u', 'n', 'n', 0, 0, -1, A, 1, B, 1, X, 1, R1, R2,
411 $ W, IW, INFO )
412 CALL CHKXER( 'stbrfs', INFOT, NOUT, LERR, OK )
413 INFOT = 8
414 CALL STBRFS( 'u', 'n', 'N', 2, 1, 1, a, 1, b, 2, x, 2, r1, r2,
415 $ w, iw, info )
416 CALL chkxer( 'STBRFS', infot, nout, lerr, ok )
417 infot = 10
418 CALL stbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 1, x, 2, r1, r2,
419 $ w, iw, info )
420 CALL chkxer( 'STBRFS', infot, nout, lerr, ok )
421 infot = 12
422 CALL stbrfs( 'U', 'N', 'N', 2, 1, 1, a, 2, b, 2, x, 1, r1, r2,
423 $ w, iw, info )
424 CALL chkxer( 'STBRFS', infot, nout, lerr, ok )
425*
426* STBCON
427*
428 srnamt = 'STBCON'
429 infot = 1
430 CALL stbcon( '/', 'U', 'N', 0, 0, a, 1, rcond, w, iw, info )
431 CALL chkxer( 'STBCON', infot, nout, lerr, ok )
432 infot = 2
433 CALL stbcon( '1', '/', 'N', 0, 0, a, 1, rcond, w, iw, info )
434 CALL chkxer( 'STBCON', infot, nout, lerr, ok )
435 infot = 3
436 CALL stbcon( '1', 'U', '/', 0, 0, a, 1, rcond, w, iw, info )
437 CALL chkxer( 'STBCON', infot, nout, lerr, ok )
438 infot = 4
439 CALL stbcon( '1', 'U', 'N', -1, 0, a, 1, rcond, w, iw, info )
440 CALL chkxer( 'STBCON', infot, nout, lerr, ok )
441 infot = 5
442 CALL stbcon( '1', 'U', 'N', 0, -1, a, 1, rcond, w, iw, info )
443 CALL chkxer( 'stbcon', INFOT, NOUT, LERR, OK )
444 INFOT = 7
445 CALL STBCON( '1', 'u', 'n', 2, 1, A, 1, RCOND, W, IW, INFO )
446 CALL CHKXER( 'stbcon', INFOT, NOUT, LERR, OK )
447*
448* SLATBS
449*
450 SRNAMT = 'slatbs'
451 INFOT = 1
452 CALL SLATBS( '/', 'n', 'n', 'n', 0, 0, A, 1, X, SCALE, W,
453 $ INFO )
454 CALL CHKXER( 'slatbs', INFOT, NOUT, LERR, OK )
455 INFOT = 2
456 CALL SLATBS( 'u', '/', 'N', 'N', 0, 0, a, 1, x, scale, w,
457 $ info )
458 CALL chkxer( 'SLATBS', infot, nout, lerr, ok )
459 infot = 3
460 CALL slatbs( 'U', 'N', '/', 'N', 0, 0, a, 1, x, scale, w,
461 $ info )
462 CALL chkxer( 'SLATBS', infot, nout, lerr, ok )
463 infot = 4
464 CALL slatbs( 'U', 'N', 'N', '/', 0, 0, a, 1, x, scale, w,
465 $ info )
466 CALL chkxer( 'SLATBS', infot, nout, lerr, ok )
467 infot = 5
468 CALL slatbs( 'U', 'N', 'N', 'N', -1, 0, a, 1, x, scale, w,
469 $ info )
470 CALL chkxer( 'SLATBS', infot, nout, lerr, ok )
471 infot = 6
472 CALL slatbs( 'U', 'N', 'N', 'N', 1, -1, a, 1, x, scale, w,
473 $ info )
474 CALL chkxer( 'slatbs', INFOT, NOUT, LERR, OK )
475 INFOT = 8
476 CALL SLATBS( 'u', 'n', 'n', 'n', 2, 1, A, 1, X, SCALE, W,
477 $ INFO )
478 CALL CHKXER( 'slatbs', INFOT, NOUT, LERR, OK )
479 END IF
480*
481* Print a summary line.
482*
483 CALL ALAESM( PATH, OK, NOUT )
484*
485 RETURN
486*
487* End of SERRTR
488*
489 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine slatbs(uplo, trans, diag, normin, n, kd, ab, ldab, x, scale, cnorm, info)
SLATBS solves a triangular banded system of equations.
Definition slatbs.f:242
subroutine slatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
SLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition slatrs.f:238
subroutine slatps(uplo, trans, diag, normin, n, ap, x, scale, cnorm, info)
SLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition slatps.f:229
subroutine stbtrs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, info)
STBTRS
Definition stbtrs.f:146
subroutine stbrfs(uplo, trans, diag, n, kd, nrhs, ab, ldab, b, ldb, x, ldx, ferr, berr, work, iwork, info)
STBRFS
Definition stbrfs.f:188
subroutine stptrs(uplo, trans, diag, n, nrhs, ap, b, ldb, info)
STPTRS
Definition stptrs.f:130
subroutine strti2(uplo, diag, n, a, lda, info)
STRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
Definition strti2.f:110
subroutine strtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
STRTRS
Definition strtrs.f:140
subroutine stprfs(uplo, trans, diag, n, nrhs, ap, b, ldb, x, ldx, ferr, berr, work, iwork, info)
STPRFS
Definition stprfs.f:175
subroutine stptri(uplo, diag, n, ap, info)
STPTRI
Definition stptri.f:117
subroutine strtri(uplo, diag, n, a, lda, info)
STRTRI
Definition strtri.f:109
subroutine strcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)
STRCON
Definition strcon.f:137
subroutine stpcon(norm, uplo, diag, n, ap, rcond, work, iwork, info)
STPCON
Definition stpcon.f:130
subroutine stbcon(norm, uplo, diag, n, kd, ab, ldab, rcond, work, iwork, info)
STBCON
Definition stbcon.f:143
subroutine strrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)
STRRFS
Definition strrfs.f:182
subroutine serrtr(path, nunit)
SERRTR
Definition serrtr.f:55