LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
alaerh.f
Go to the documentation of this file.
1 *> \brief \b ALAERH
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 ALAERH( PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU,
12 * N5, IMAT, NFAIL, NERRS, NOUT )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER*3 PATH
16 * CHARACTER*( * ) SUBNAM
17 * CHARACTER*( * ) OPTS
18 * INTEGER IMAT, INFO, INFOE, KL, KU, M, N, N5, NERRS,
19 * $ NFAIL, NOUT
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> ALAERH is an error handler for the LAPACK routines. It prints the
29 *> header if this is the first error message and prints the error code
30 *> and form of recovery, if any. The character evaluations in this
31 *> routine may make it slow, but it should not be called once the LAPACK
32 *> routines are fully debugged.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] PATH
39 *> \verbatim
40 *> PATH is CHARACTER*3
41 *> The LAPACK path name of subroutine SUBNAM.
42 *> \endverbatim
43 *>
44 *> \param[in] SUBNAM
45 *> \verbatim
46 *> SUBNAM is CHARACTER*(*)
47 *> The name of the subroutine that returned an error code.
48 *> \endverbatim
49 *>
50 *> \param[in] INFO
51 *> \verbatim
52 *> INFO is INTEGER
53 *> The error code returned from routine SUBNAM.
54 *> \endverbatim
55 *>
56 *> \param[in] INFOE
57 *> \verbatim
58 *> INFOE is INTEGER
59 *> The expected error code from routine SUBNAM, if SUBNAM were
60 *> error-free. If INFOE = 0, an error message is printed, but
61 *> if INFOE.NE.0, we assume only the return code INFO is wrong.
62 *> \endverbatim
63 *>
64 *> \param[in] OPTS
65 *> \verbatim
66 *> OPTS is CHARACTER*(*)
67 *> The character options to the subroutine SUBNAM, concatenated
68 *> into a single character string. For example, UPLO = 'U',
69 *> TRANS = 'T', and DIAG = 'N' for a triangular routine would
70 *> be specified as OPTS = 'UTN'.
71 *> \endverbatim
72 *>
73 *> \param[in] M
74 *> \verbatim
75 *> M is INTEGER
76 *> The matrix row dimension.
77 *> \endverbatim
78 *>
79 *> \param[in] N
80 *> \verbatim
81 *> N is INTEGER
82 *> The matrix column dimension. Accessed only if PATH = xGE or
83 *> xGB.
84 *> \endverbatim
85 *>
86 *> \param[in] KL
87 *> \verbatim
88 *> KL is INTEGER
89 *> The number of sub-diagonals of the matrix. Accessed only if
90 *> PATH = xGB, xPB, or xTB. Also used for NRHS for PATH = xLS.
91 *> \endverbatim
92 *>
93 *> \param[in] KU
94 *> \verbatim
95 *> KU is INTEGER
96 *> The number of super-diagonals of the matrix. Accessed only
97 *> if PATH = xGB.
98 *> \endverbatim
99 *>
100 *> \param[in] N5
101 *> \verbatim
102 *> N5 is INTEGER
103 *> A fifth integer parameter, may be the blocksize NB or the
104 *> number of right hand sides NRHS.
105 *> \endverbatim
106 *>
107 *> \param[in] IMAT
108 *> \verbatim
109 *> IMAT is INTEGER
110 *> The matrix type.
111 *> \endverbatim
112 *>
113 *> \param[in] NFAIL
114 *> \verbatim
115 *> NFAIL is INTEGER
116 *> The number of prior tests that did not pass the threshold;
117 *> used to determine if the header should be printed.
118 *> \endverbatim
119 *>
120 *> \param[in,out] NERRS
121 *> \verbatim
122 *> NERRS is INTEGER
123 *> On entry, the number of errors already detected; used to
124 *> determine if the header should be printed.
125 *> On exit, NERRS is increased by 1.
126 *> \endverbatim
127 *>
128 *> \param[in] NOUT
129 *> \verbatim
130 *> NOUT is INTEGER
131 *> The unit number on which results are to be printed.
132 *> \endverbatim
133 *
134 * Authors:
135 * ========
136 *
137 *> \author Univ. of Tennessee
138 *> \author Univ. of California Berkeley
139 *> \author Univ. of Colorado Denver
140 *> \author NAG Ltd.
141 *
142 *> \date December 2016
143 *
144 *> \ingroup aux_lin
145 *
146 * =====================================================================
147  SUBROUTINE alaerh( PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU,
148  $ n5, imat, nfail, nerrs, nout )
149 *
150 * -- LAPACK test routine (version 3.7.0) --
151 * -- LAPACK is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * December 2016
154 *
155 * .. Scalar Arguments ..
156  CHARACTER*3 PATH
157  CHARACTER*( * ) SUBNAM
158  CHARACTER*( * ) OPTS
159  INTEGER IMAT, INFO, INFOE, KL, KU, M, N, N5, NERRS,
160  $ nfail, nout
161 * ..
162 *
163 * =====================================================================
164 *
165 * .. Local Scalars ..
166  CHARACTER UPLO
167  CHARACTER*2 P2
168  CHARACTER*3 C3
169 * ..
170 * .. External Functions ..
171  LOGICAL LSAME, LSAMEN
172  EXTERNAL lsame, lsamen
173 * ..
174 * .. Intrinsic Functions ..
175  INTRINSIC len_trim
176 * ..
177 * .. External Subroutines ..
178  EXTERNAL aladhd, alahd
179 * ..
180 * .. Executable Statements ..
181 *
182  IF( info.EQ.0 )
183  $ RETURN
184  p2 = path( 2: 3 )
185  c3 = subnam( 4: 6 )
186 *
187 * Print the header if this is the first error message.
188 *
189  IF( nfail.EQ.0 .AND. nerrs.EQ.0 ) THEN
190  IF( lsamen( 3, c3, 'SV ' ) .OR. lsamen( 3, c3, 'SVX' ) ) THEN
191  CALL aladhd( nout, path )
192  ELSE
193  CALL alahd( nout, path )
194  END IF
195  END IF
196  nerrs = nerrs + 1
197 *
198 * Print the message detailing the error and form of recovery,
199 * if any.
200 *
201  IF( lsamen( 2, p2, 'GE' ) ) THEN
202 *
203 * xGE: General matrices
204 *
205  IF( lsamen( 3, c3, 'TRF' ) ) THEN
206  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
207  WRITE( nout, fmt = 9988 )
208  $ subnam(1:len_trim( subnam )), info, infoe, m, n, n5,
209  $ imat
210  ELSE
211  WRITE( nout, fmt = 9975 )
212  $ subnam(1:len_trim( subnam )), info, m, n, n5, imat
213  END IF
214  IF( info.NE.0 )
215  $ WRITE( nout, fmt = 9949 )
216 *
217  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
218 *
219  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
220  WRITE( nout, fmt = 9984 )
221  $ subnam(1:len_trim( subnam )), info, infoe, n, n5,
222  $ imat
223  ELSE
224  WRITE( nout, fmt = 9970 )
225  $ subnam(1:len_trim( subnam )), info, n, n5, imat
226  END IF
227 *
228  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
229 *
230  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
231  WRITE( nout, fmt = 9992 )
232  $ subnam(1:len_trim( subnam )), info, infoe,
233  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
234  ELSE
235  WRITE( nout, fmt = 9997 )
236  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
237  $ opts( 2: 2 ), n, n5, imat
238  END IF
239 *
240  ELSE IF( lsamen( 3, c3, 'TRI' ) ) THEN
241 *
242  WRITE( nout, fmt = 9971 )
243  $ subnam(1:len_trim( subnam )), info, n, n5, imat
244 *
245  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
246 *
247  WRITE( nout, fmt = 9978 )
248  $ subnam(1:len_trim( subnam )), info, m, n, imat
249 *
250  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
251 *
252  WRITE( nout, fmt = 9969 )
253  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m,
254  $ imat
255 *
256  ELSE IF( lsamen( 3, c3, 'LS ' ) ) THEN
257 *
258  WRITE( nout, fmt = 9965 )
259  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, n,
260  $ kl, n5, imat
261 *
262  ELSE IF( lsamen( 3, c3, 'LSX' ) .OR. lsamen( 3, c3, 'LSS' ) )
263  $ THEN
264 *
265  WRITE( nout, fmt = 9974 )
266  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
267 *
268  ELSE
269 *
270  WRITE( nout, fmt = 9963 )
271  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, n5,
272  $ imat
273  END IF
274 *
275  ELSE IF( lsamen( 2, p2, 'GB' ) ) THEN
276 *
277 * xGB: General band matrices
278 *
279  IF( lsamen( 3, c3, 'TRF' ) ) THEN
280  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
281  WRITE( nout, fmt = 9989 )
282  $ subnam(1:len_trim( subnam )), info, infoe, m, n, kl,
283  $ ku, n5, imat
284  ELSE
285  WRITE( nout, fmt = 9976 )
286  $ subnam(1:len_trim( subnam )), info, m, n, kl, ku, n5,
287  $ imat
288  END IF
289  IF( info.NE.0 )
290  $ WRITE( nout, fmt = 9949 )
291 *
292  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
293 *
294  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
295  WRITE( nout, fmt = 9986 )
296  $ subnam(1:len_trim( subnam )), info, infoe, n, kl, ku,
297  $ n5, imat
298  ELSE
299  WRITE( nout, fmt = 9972 )
300  $ subnam(1:len_trim( subnam )), info, n, kl, ku, n5,
301  $ imat
302  END IF
303 *
304  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
305 *
306  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
307  WRITE( nout, fmt = 9993 )
308  $ subnam(1:len_trim( subnam )), info, infoe,
309  $ opts( 1: 1 ), opts( 2: 2 ), n, kl, ku, n5, imat
310  ELSE
311  WRITE( nout, fmt = 9998 )
312  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
313  $ opts( 2: 2 ), n, kl, ku, n5, imat
314  END IF
315 *
316  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
317 *
318  WRITE( nout, fmt = 9977 )
319  $ subnam(1:len_trim( subnam )), info, m, n, kl, ku, imat
320 *
321  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
322 *
323  WRITE( nout, fmt = 9968 )
324  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, kl,
325  $ ku, imat
326 *
327  ELSE
328 *
329  WRITE( nout, fmt = 9964 )
330  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, kl,
331  $ ku, n5, imat
332  END IF
333 *
334  ELSE IF( lsamen( 2, p2, 'GT' ) ) THEN
335 *
336 * xGT: General tridiagonal matrices
337 *
338  IF( lsamen( 3, c3, 'TRF' ) ) THEN
339  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
340  WRITE( nout, fmt = 9987 )
341  $ subnam(1:len_trim( subnam )), info, infoe, n, imat
342  ELSE
343  WRITE( nout, fmt = 9973 )
344  $ subnam(1:len_trim( subnam )), info, n, imat
345  END IF
346  IF( info.NE.0 )
347  $ WRITE( nout, fmt = 9949 )
348 *
349  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
350 *
351  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
352  WRITE( nout, fmt = 9984 )
353  $ subnam(1:len_trim( subnam )), info, infoe, n, n5,
354  $ imat
355  ELSE
356  WRITE( nout, fmt = 9970 )
357  $ subnam(1:len_trim( subnam )), info, n, n5, imat
358  END IF
359 *
360  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
361 *
362  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
363  WRITE( nout, fmt = 9992 )
364  $ subnam(1:len_trim( subnam )), info, infoe,
365  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
366  ELSE
367  WRITE( nout, fmt = 9997 )
368  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
369  $ opts( 2: 2 ), n, n5, imat
370  END IF
371 *
372  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
373 *
374  WRITE( nout, fmt = 9969 )
375  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m,
376  $ imat
377 *
378  ELSE
379 *
380  WRITE( nout, fmt = 9963 )
381  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, n5,
382  $ imat
383  END IF
384 *
385  ELSE IF( lsamen( 2, p2, 'PO' ) ) THEN
386 *
387 * xPO: Symmetric or Hermitian positive definite matrices
388 *
389  uplo = opts( 1: 1 )
390  IF( lsamen( 3, c3, 'TRF' ) ) THEN
391  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
392  WRITE( nout, fmt = 9980 )
393  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
394  $ n5, imat
395  ELSE
396  WRITE( nout, fmt = 9956 )
397  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
398  END IF
399  IF( info.NE.0 )
400  $ WRITE( nout, fmt = 9949 )
401 *
402  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
403 *
404  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
405  WRITE( nout, fmt = 9979 )
406  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
407  $ n5, imat
408  ELSE
409  WRITE( nout, fmt = 9955 )
410  $ subnam(1:len_trim( subnam )), info, uplo, n, n5, imat
411  END IF
412 *
413  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
414 *
415  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
416  WRITE( nout, fmt = 9990 )
417  $ subnam(1:len_trim( subnam )), info, infoe,
418  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
419  ELSE
420  WRITE( nout, fmt = 9995 )
421  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
422  $ opts( 2: 2 ), n, n5, imat
423  END IF
424 *
425  ELSE IF( lsamen( 3, c3, 'TRI' ) ) THEN
426 *
427  WRITE( nout, fmt = 9956 )
428  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
429 *
430  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
431  $ lsamen( 3, c3, 'CON' ) ) THEN
432 *
433  WRITE( nout, fmt = 9960 )
434  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
435 *
436  ELSE
437 *
438  WRITE( nout, fmt = 9955 )
439  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
440  END IF
441 *
442  ELSE IF( lsamen( 2, p2, 'PS' ) ) THEN
443 *
444 * xPS: Symmetric or Hermitian positive semi-definite matrices
445 *
446  uplo = opts( 1: 1 )
447  IF( lsamen( 3, c3, 'TRF' ) ) THEN
448  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
449  WRITE( nout, fmt = 9980 )subnam, info, infoe, uplo, m,
450  $ n5, imat
451  ELSE
452  WRITE( nout, fmt = 9956 )subnam, info, uplo, m, n5, imat
453  END IF
454  IF( info.NE.0 )
455  $ WRITE( nout, fmt = 9949 )
456 *
457  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
458 *
459  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
460  WRITE( nout, fmt = 9979 )subnam, info, infoe, uplo, n,
461  $ n5, imat
462  ELSE
463  WRITE( nout, fmt = 9955 )subnam, info, uplo, n, n5, imat
464  END IF
465 *
466  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
467 *
468  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
469  WRITE( nout, fmt = 9990 )subnam, info, infoe,
470  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
471  ELSE
472  WRITE( nout, fmt = 9995 )subnam, info, opts( 1: 1 ),
473  $ opts( 2: 2 ), n, n5, imat
474  END IF
475 *
476  ELSE IF( lsamen( 3, c3, 'TRI' ) ) THEN
477 *
478  WRITE( nout, fmt = 9956 )subnam, info, uplo, m, n5, imat
479 *
480  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMT' ) .OR.
481  $ lsamen( 3, c3, 'CON' ) ) THEN
482 *
483  WRITE( nout, fmt = 9960 )subnam, info, uplo, m, imat
484 *
485  ELSE
486 *
487  WRITE( nout, fmt = 9955 )subnam, info, uplo, m, n5, imat
488  END IF
489 *
490  ELSE IF( lsamen( 2, p2, 'SY' )
491  $ .OR. lsamen( 2, p2, 'SR' )
492  $ .OR. lsamen( 2, p2, 'SK' )
493  $ .OR. lsamen( 2, p2, 'HE' )
494  $ .OR. lsamen( 2, p2, 'HR' )
495  $ .OR. lsamen( 2, p2, 'HK' )
496  $ .OR. lsamen( 2, p2, 'HA' ) ) THEN
497 *
498 * xSY: symmetric indefinite matrices
499 * with partial (Bunch-Kaufman) pivoting;
500 * xSR: symmetric indefinite matrices
501 * with rook (bounded Bunch-Kaufman) pivoting;
502 * xSK: symmetric indefinite matrices
503 * with rook (bounded Bunch-Kaufman) pivoting,
504 * new storage format;
505 * xHE: Hermitian indefinite matrices
506 * with partial (Bunch-Kaufman) pivoting.
507 * xHR: Hermitian indefinite matrices
508 * with rook (bounded Bunch-Kaufman) pivoting;
509 * xHK: Hermitian indefinite matrices
510 * with rook (bounded Bunch-Kaufman) pivoting,
511 * new storage format;
512 * xHA: Hermitian matrices
513 * Aasen Algorithm
514 *
515  uplo = opts( 1: 1 )
516  IF( lsamen( 3, c3, 'TRF' ) ) THEN
517  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
518  WRITE( nout, fmt = 9980 )
519  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
520  $ n5, imat
521  ELSE
522  WRITE( nout, fmt = 9956 )
523  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
524  END IF
525  IF( info.NE.0 )
526  $ WRITE( nout, fmt = 9949 )
527 *
528  ELSE IF( lsamen( 2, c3, 'SV' ) ) THEN
529 *
530  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
531  WRITE( nout, fmt = 9979 )
532  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
533  $ n5, imat
534  ELSE
535  WRITE( nout, fmt = 9955 )
536  $ subnam(1:len_trim( subnam )), info, uplo, n, n5, imat
537  END IF
538 *
539  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
540 *
541  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
542  WRITE( nout, fmt = 9990 )
543  $ subnam(1:len_trim( subnam )), info, infoe,
544  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
545  ELSE
546  WRITE( nout, fmt = 9995 )
547  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
548  $ opts( 2: 2 ), n, n5, imat
549  END IF
550 *
551  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
552  $ lsamen( 3, c3, 'TRI' ) .OR. lsamen( 3, c3, 'CON' ) )
553  $ THEN
554 *
555  WRITE( nout, fmt = 9960 )
556  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
557 *
558  ELSE
559 *
560  WRITE( nout, fmt = 9955 )
561  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
562  END IF
563 *
564  ELSE IF( lsamen( 2, p2, 'PP' ) .OR. lsamen( 2, p2, 'SP' ) .OR.
565  $ lsamen( 2, p2, 'HP' ) ) THEN
566 *
567 * xPP, xHP, or xSP: Symmetric or Hermitian packed matrices
568 *
569  uplo = opts( 1: 1 )
570  IF( lsamen( 3, c3, 'TRF' ) ) THEN
571  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
572  WRITE( nout, fmt = 9983 )
573  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
574  $ imat
575  ELSE
576  WRITE( nout, fmt = 9960 )
577  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
578  END IF
579  IF( info.NE.0 )
580  $ WRITE( nout, fmt = 9949 )
581 *
582  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
583 *
584  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
585  WRITE( nout, fmt = 9979 )
586  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
587  $ n5, imat
588  ELSE
589  WRITE( nout, fmt = 9955 )
590  $ subnam(1:len_trim( subnam )), info, uplo, n, n5, imat
591  END IF
592 *
593  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
594 *
595  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
596  WRITE( nout, fmt = 9990 )
597  $ subnam(1:len_trim( subnam )), info, infoe,
598  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
599  ELSE
600  WRITE( nout, fmt = 9995 )
601  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
602  $ opts( 2: 2 ), n, n5, imat
603  END IF
604 *
605  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
606  $ lsamen( 3, c3, 'TRI' ) .OR. lsamen( 3, c3, 'CON' ) )
607  $ THEN
608 *
609  WRITE( nout, fmt = 9960 )
610  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
611 *
612  ELSE
613 *
614  WRITE( nout, fmt = 9955 )
615  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
616  END IF
617 *
618  ELSE IF( lsamen( 2, p2, 'PB' ) ) THEN
619 *
620 * xPB: Symmetric (Hermitian) positive definite band matrix
621 *
622  uplo = opts( 1: 1 )
623  IF( lsamen( 3, c3, 'TRF' ) ) THEN
624  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
625  WRITE( nout, fmt = 9982 )
626  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
627  $ kl, n5, imat
628  ELSE
629  WRITE( nout, fmt = 9958 )
630  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, n5,
631  $ imat
632  END IF
633  IF( info.NE.0 )
634  $ WRITE( nout, fmt = 9949 )
635 *
636  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
637 *
638  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
639  WRITE( nout, fmt = 9981 )
640  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
641  $ kl, n5, imat
642  ELSE
643  WRITE( nout, fmt = 9957 )
644  $ subnam(1:len_trim( subnam )), info, uplo, n, kl, n5,
645  $ imat
646  END IF
647 *
648  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
649 *
650  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
651  WRITE( nout, fmt = 9991 )
652  $ subnam(1:len_trim( subnam )), info, infoe,
653  $ opts( 1: 1 ), opts( 2: 2 ), n, kl, n5, imat
654  ELSE
655  WRITE( nout, fmt = 9996 )
656  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
657  $ opts( 2: 2 ), n, kl, n5, imat
658  END IF
659 *
660  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
661  $ lsamen( 3, c3, 'CON' ) ) THEN
662 *
663  WRITE( nout, fmt = 9959 )
664  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, imat
665 *
666  ELSE
667 *
668  WRITE( nout, fmt = 9957 )
669  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, n5,
670  $ imat
671  END IF
672 *
673  ELSE IF( lsamen( 2, p2, 'PT' ) ) THEN
674 *
675 * xPT: Positive definite tridiagonal matrices
676 *
677  IF( lsamen( 3, c3, 'TRF' ) ) THEN
678  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
679  WRITE( nout, fmt = 9987 )
680  $ subnam(1:len_trim( subnam )), info, infoe, n, imat
681  ELSE
682  WRITE( nout, fmt = 9973 )
683  $ subnam(1:len_trim( subnam )), info, n, imat
684  END IF
685  IF( info.NE.0 )
686  $ WRITE( nout, fmt = 9949 )
687 *
688  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
689 *
690  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
691  WRITE( nout, fmt = 9984 )
692  $ subnam(1:len_trim( subnam )), info, infoe, n, n5,
693  $ imat
694  ELSE
695  WRITE( nout, fmt = 9970 )
696  $ subnam(1:len_trim( subnam )), info, n, n5, imat
697  END IF
698 *
699  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
700 *
701  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
702  WRITE( nout, fmt = 9994 )
703  $ subnam(1:len_trim( subnam )), info, infoe,
704  $ opts( 1: 1 ), n, n5, imat
705  ELSE
706  WRITE( nout, fmt = 9999 )
707  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), n,
708  $ n5, imat
709  END IF
710 *
711  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
712 *
713  IF( lsame( subnam( 1: 1 ), 'S' ) .OR.
714  $ lsame( subnam( 1: 1 ), 'D' ) ) THEN
715  WRITE( nout, fmt = 9973 )
716  $ subnam(1:len_trim( subnam )), info, m, imat
717  ELSE
718  WRITE( nout, fmt = 9969 )
719  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m,
720  $ imat
721  END IF
722 *
723  ELSE
724 *
725  WRITE( nout, fmt = 9963 )
726  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, n5,
727  $ imat
728  END IF
729 *
730  ELSE IF( lsamen( 2, p2, 'TR' ) ) THEN
731 *
732 * xTR: Triangular matrix
733 *
734  IF( lsamen( 3, c3, 'TRI' ) ) THEN
735  WRITE( nout, fmt = 9961 )
736  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
737  $ opts( 2: 2 ), m, n5, imat
738  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
739  WRITE( nout, fmt = 9967 )
740  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
741  $ opts( 2: 2 ), opts( 3: 3 ), m, imat
742  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATRS' ) ) THEN
743  WRITE( nout, fmt = 9952 )
744  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
745  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, imat
746  ELSE
747  WRITE( nout, fmt = 9953 )
748  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
749  $ opts( 2: 2 ), opts( 3: 3 ), m, n5, imat
750  END IF
751 *
752  ELSE IF( lsamen( 2, p2, 'TP' ) ) THEN
753 *
754 * xTP: Triangular packed matrix
755 *
756  IF( lsamen( 3, c3, 'TRI' ) ) THEN
757  WRITE( nout, fmt = 9962 )
758  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
759  $ opts( 2: 2 ), m, imat
760  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
761  WRITE( nout, fmt = 9967 )
762  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
763  $ opts( 2: 2 ), opts( 3: 3 ), m, imat
764  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATPS' ) ) THEN
765  WRITE( nout, fmt = 9952 )
766  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
767  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, imat
768  ELSE
769  WRITE( nout, fmt = 9953 )
770  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
771  $ opts( 2: 2 ), opts( 3: 3 ), m, n5, imat
772  END IF
773 *
774  ELSE IF( lsamen( 2, p2, 'TB' ) ) THEN
775 *
776 * xTB: Triangular band matrix
777 *
778  IF( lsamen( 3, c3, 'CON' ) ) THEN
779  WRITE( nout, fmt = 9966 )
780  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
781  $ opts( 2: 2 ), opts( 3: 3 ), m, kl, imat
782  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATBS' ) ) THEN
783  WRITE( nout, fmt = 9951 )
784  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
785  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, kl, imat
786  ELSE
787  WRITE( nout, fmt = 9954 )
788  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
789  $ opts( 2: 2 ), opts( 3: 3 ), m, kl, n5, imat
790  END IF
791 *
792  ELSE IF( lsamen( 2, p2, 'QR' ) ) THEN
793 *
794 * xQR: QR factorization
795 *
796  IF( lsamen( 3, c3, 'QRS' ) ) THEN
797  WRITE( nout, fmt = 9974 )
798  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
799  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
800  WRITE( nout, fmt = 9978 )
801  $ subnam(1:len_trim( subnam )), info, m, n, imat
802  END IF
803 *
804  ELSE IF( lsamen( 2, p2, 'LQ' ) ) THEN
805 *
806 * xLQ: LQ factorization
807 *
808  IF( lsamen( 3, c3, 'LQS' ) ) THEN
809  WRITE( nout, fmt = 9974 )
810  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
811  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
812  WRITE( nout, fmt = 9978 )
813  $ subnam(1:len_trim( subnam )), info, m, n, imat
814  END IF
815 *
816  ELSE IF( lsamen( 2, p2, 'QL' ) ) THEN
817 *
818 * xQL: QL factorization
819 *
820  IF( lsamen( 3, c3, 'QLS' ) ) THEN
821  WRITE( nout, fmt = 9974 )
822  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
823  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
824  WRITE( nout, fmt = 9978 )
825  $ subnam(1:len_trim( subnam )), info, m, n, imat
826  END IF
827 *
828  ELSE IF( lsamen( 2, p2, 'RQ' ) ) THEN
829 *
830 * xRQ: RQ factorization
831 *
832  IF( lsamen( 3, c3, 'RQS' ) ) THEN
833  WRITE( nout, fmt = 9974 )
834  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
835  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
836  WRITE( nout, fmt = 9978 )
837  $ subnam(1:len_trim( subnam )), info, m, n, imat
838  END IF
839 *
840  ELSE IF( lsamen( 2, p2, 'LU' ) ) THEN
841 *
842  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
843  WRITE( nout, fmt = 9988 )
844  $ subnam(1:len_trim( subnam )), info, infoe, m, n, n5,
845  $ imat
846  ELSE
847  WRITE( nout, fmt = 9975 )
848  $ subnam(1:len_trim( subnam )), info, m, n, n5, imat
849  END IF
850 *
851  ELSE IF( lsamen( 2, p2, 'CH' ) ) THEN
852 *
853  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
854  WRITE( nout, fmt = 9985 )
855  $ subnam(1:len_trim( subnam )), info, infoe, m, n5, imat
856  ELSE
857  WRITE( nout, fmt = 9971 )
858  $ subnam(1:len_trim( subnam )), info, m, n5, imat
859  END IF
860 *
861  ELSE
862 *
863 * Print a generic message if the path is unknown.
864 *
865  WRITE( nout, fmt = 9950 )
866  $ subnam(1:len_trim( subnam )), info
867  END IF
868 *
869 * Description of error message (alphabetical, left to right)
870 *
871 * SUBNAM, INFO, FACT, N, NRHS, IMAT
872 *
873  9999 FORMAT( ' *** Error code from ', a, '=', i5, ', FACT=''', a1,
874  $ ''', N=', i5, ', NRHS=', i4, ', type ', i2 )
875 *
876 * SUBNAM, INFO, FACT, TRANS, N, KL, KU, NRHS, IMAT
877 *
878  9998 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
879  $ a1, ''', TRANS=''', a1, ''', N=', i5, ', KL=', i5, ', KU=',
880  $ i5, ', NRHS=', i4, ', type ', i1 )
881 *
882 * SUBNAM, INFO, FACT, TRANS, N, NRHS, IMAT
883 *
884  9997 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
885  $ a1, ''', TRANS=''', a1, ''', N =', i5, ', NRHS =', i4,
886  $ ', type ', i2 )
887 *
888 * SUBNAM, INFO, FACT, UPLO, N, KD, NRHS, IMAT
889 *
890  9996 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
891  $ a1, ''', UPLO=''', a1, ''', N=', i5, ', KD=', i5, ', NRHS=',
892  $ i4, ', type ', i2 )
893 *
894 * SUBNAM, INFO, FACT, UPLO, N, NRHS, IMAT
895 *
896  9995 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
897  $ a1, ''', UPLO=''', a1, ''', N =', i5, ', NRHS =', i4,
898  $ ', type ', i2 )
899 *
900 * SUBNAM, INFO, INFOE, FACT, N, NRHS, IMAT
901 *
902  9994 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
903  $ i2, / ' ==> FACT=''', a1, ''', N =', i5, ', NRHS =', i4,
904  $ ', type ', i2 )
905 *
906 * SUBNAM, INFO, INFOE, FACT, TRANS, N, KL, KU, NRHS, IMAT
907 *
908  9993 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
909  $ i2, / ' ==> FACT=''', a1, ''', TRANS=''', a1, ''', N=', i5,
910  $ ', KL=', i5, ', KU=', i5, ', NRHS=', i4, ', type ', i1 )
911 *
912 * SUBNAM, INFO, INFOE, FACT, TRANS, N, NRHS, IMAT
913 *
914  9992 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
915  $ i2, / ' ==> FACT=''', a1, ''', TRANS=''', a1, ''', N =', i5,
916  $ ', NRHS =', i4, ', type ', i2 )
917 *
918 * SUBNAM, INFO, INFOE, FACT, UPLO, N, KD, NRHS, IMAT
919 *
920  9991 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
921  $ i2, / ' ==> FACT=''', a1, ''', UPLO=''', a1, ''', N=', i5,
922  $ ', KD=', i5, ', NRHS=', i4, ', type ', i2 )
923 *
924 * SUBNAM, INFO, INFOE, FACT, UPLO, N, NRHS, IMAT
925 *
926  9990 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
927  $ i2, / ' ==> FACT=''', a1, ''', UPLO=''', a1, ''', N =', i5,
928  $ ', NRHS =', i4, ', type ', i2 )
929 *
930 * SUBNAM, INFO, INFOE, M, N, KL, KU, NB, IMAT
931 *
932  9989 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
933  $ i2, / ' ==> M = ', i5, ', N =', i5, ', KL =', i5, ', KU =',
934  $ i5, ', NB =', i4, ', type ', i2 )
935 *
936 * SUBNAM, INFO, INFOE, M, N, NB, IMAT
937 *
938  9988 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
939  $ i2, / ' ==> M =', i5, ', N =', i5, ', NB =', i4, ', type ',
940  $ i2 )
941 *
942 * SUBNAM, INFO, INFOE, N, IMAT
943 *
944  9987 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
945  $ i2, ' for N=', i5, ', type ', i2 )
946 *
947 * SUBNAM, INFO, INFOE, N, KL, KU, NRHS, IMAT
948 *
949  9986 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
950  $ i2, / ' ==> N =', i5, ', KL =', i5, ', KU =', i5,
951  $ ', NRHS =', i4, ', type ', i2 )
952 *
953 * SUBNAM, INFO, INFOE, N, NB, IMAT
954 *
955  9985 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
956  $ i2, / ' ==> N =', i5, ', NB =', i4, ', type ', i2 )
957 *
958 * SUBNAM, INFO, INFOE, N, NRHS, IMAT
959 *
960  9984 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
961  $ i2, / ' ==> N =', i5, ', NRHS =', i4, ', type ', i2 )
962 *
963 * SUBNAM, INFO, INFOE, UPLO, N, IMAT
964 *
965  9983 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
966  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', type ', i2 )
967 *
968 * SUBNAM, INFO, INFOE, UPLO, N, KD, NB, IMAT
969 *
970  9982 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
971  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', KD =', i5,
972  $ ', NB =', i4, ', type ', i2 )
973 *
974 * SUBNAM, INFO, INFOE, UPLO, N, KD, NRHS, IMAT
975 *
976  9981 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
977  $ i2, / ' ==> UPLO=''', a1, ''', N =', i5, ', KD =', i5,
978  $ ', NRHS =', i4, ', type ', i2 )
979 *
980 * SUBNAM, INFO, INFOE, UPLO, N, NB, IMAT
981 *
982  9980 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
983  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', NB =', i4,
984  $ ', type ', i2 )
985 *
986 * SUBNAM, INFO, INFOE, UPLO, N, NRHS, IMAT
987 *
988  9979 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
989  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', NRHS =', i4,
990  $ ', type ', i2 )
991 *
992 * SUBNAM, INFO, M, N, IMAT
993 *
994  9978 FORMAT( ' *** Error code from ', a, ' =', i5, ' for M =', i5,
995  $ ', N =', i5, ', type ', i2 )
996 *
997 * SUBNAM, INFO, M, N, KL, KU, IMAT
998 *
999  9977 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> M = ', i5,
1000  $ ', N =', i5, ', KL =', i5, ', KU =', i5, ', type ', i2 )
1001 *
1002 * SUBNAM, INFO, M, N, KL, KU, NB, IMAT
1003 *
1004  9976 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> M = ', i5,
1005  $ ', N =', i5, ', KL =', i5, ', KU =', i5, ', NB =', i4,
1006  $ ', type ', i2 )
1007 *
1008 * SUBNAM, INFO, M, N, NB, IMAT
1009 *
1010  9975 FORMAT( ' *** Error code from ', a, '=', i5, ' for M=', i5,
1011  $ ', N=', i5, ', NB=', i4, ', type ', i2 )
1012 *
1013 * SUBNAM, INFO, M, N, NRHS, NB, IMAT
1014 *
1015  9974 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> M =', i5,
1016  $ ', N =', i5, ', NRHS =', i4, ', NB =', i4, ', type ', i2 )
1017 *
1018 * SUBNAM, INFO, N, IMAT
1019 *
1020  9973 FORMAT( ' *** Error code from ', a, ' =', i5, ' for N =', i5,
1021  $ ', type ', i2 )
1022 *
1023 * SUBNAM, INFO, N, KL, KU, NRHS, IMAT
1024 *
1025  9972 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> N =', i5,
1026  $ ', KL =', i5, ', KU =', i5, ', NRHS =', i4, ', type ', i2 )
1027 *
1028 * SUBNAM, INFO, N, NB, IMAT
1029 *
1030  9971 FORMAT( ' *** Error code from ', a, '=', i5, ' for N=', i5,
1031  $ ', NB=', i4, ', type ', i2 )
1032 *
1033 * SUBNAM, INFO, N, NRHS, IMAT
1034 *
1035  9970 FORMAT( ' *** Error code from ', a, ' =', i5, ' for N =', i5,
1036  $ ', NRHS =', i4, ', type ', i2 )
1037 *
1038 * SUBNAM, INFO, NORM, N, IMAT
1039 *
1040  9969 FORMAT( ' *** Error code from ', a, ' =', i5, ' for NORM = ''',
1041  $ a1, ''', N =', i5, ', type ', i2 )
1042 *
1043 * SUBNAM, INFO, NORM, N, KL, KU, IMAT
1044 *
1045  9968 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM =''',
1046  $ a1, ''', N =', i5, ', KL =', i5, ', KU =', i5, ', type ',
1047  $ i2 )
1048 *
1049 * SUBNAM, INFO, NORM, UPLO, DIAG, N, IMAT
1050 *
1051  9967 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM=''',
1052  $ a1, ''', UPLO =''', a1, ''', DIAG=''', a1, ''', N =', i5,
1053  $ ', type ', i2 )
1054 *
1055 * SUBNAM, INFO, NORM, UPLO, DIAG, N, KD, IMAT
1056 *
1057  9966 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM=''',
1058  $ a1, ''', UPLO =''', a1, ''', DIAG=''', a1, ''', N=', i5,
1059  $ ', KD=', i5, ', type ', i2 )
1060 *
1061 * SUBNAM, INFO, TRANS, M, N, NRHS, NB, IMAT
1062 *
1063  9965 FORMAT( ' *** Error code from ', a, ' =', i5,
1064  $ / ' ==> TRANS = ''', a1, ''', M =', i5, ', N =', i5,
1065  $ ', NRHS =', i4, ', NB =', i4, ', type ', i2 )
1066 *
1067 * SUBNAM, INFO, TRANS, N, KL, KU, NRHS, IMAT
1068 *
1069  9964 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> TRANS=''',
1070  $ a1, ''', N =', i5, ', KL =', i5, ', KU =', i5, ', NRHS =',
1071  $ i4, ', type ', i2 )
1072 *
1073 * SUBNAM, INFO, TRANS, N, NRHS, IMAT
1074 *
1075  9963 FORMAT( ' *** Error code from ', a, ' =', i5,
1076  $ / ' ==> TRANS = ''', a1, ''', N =', i5, ', NRHS =', i4,
1077  $ ', type ', i2 )
1078 *
1079 * SUBNAM, INFO, UPLO, DIAG, N, IMAT
1080 *
1081  9962 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1082  $ a1, ''', DIAG =''', a1, ''', N =', i5, ', type ', i2 )
1083 *
1084 * SUBNAM, INFO, UPLO, DIAG, N, NB, IMAT
1085 *
1086  9961 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1087  $ a1, ''', DIAG =''', a1, ''', N =', i5, ', NB =', i4,
1088  $ ', type ', i2 )
1089 *
1090 * SUBNAM, INFO, UPLO, N, IMAT
1091 *
1092  9960 FORMAT( ' *** Error code from ', a, ' =', i5, ' for UPLO = ''',
1093  $ a1, ''', N =', i5, ', type ', i2 )
1094 *
1095 * SUBNAM, INFO, UPLO, N, KD, IMAT
1096 *
1097  9959 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1098  $ a1, ''', N =', i5, ', KD =', i5, ', type ', i2 )
1099 *
1100 * SUBNAM, INFO, UPLO, N, KD, NB, IMAT
1101 *
1102  9958 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1103  $ a1, ''', N =', i5, ', KD =', i5, ', NB =', i4, ', type ',
1104  $ i2 )
1105 *
1106 * SUBNAM, INFO, UPLO, N, KD, NRHS, IMAT
1107 *
1108  9957 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> UPLO = ''',
1109  $ a1, ''', N =', i5, ', KD =', i5, ', NRHS =', i4, ', type ',
1110  $ i2 )
1111 *
1112 * SUBNAM, INFO, UPLO, N, NB, IMAT
1113 *
1114  9956 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1115  $ a1, ''', N =', i5, ', NB =', i4, ', type ', i2 )
1116 *
1117 * SUBNAM, INFO, UPLO, N, NRHS, IMAT
1118 *
1119  9955 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1120  $ a1, ''', N =', i5, ', NRHS =', i4, ', type ', i2 )
1121 *
1122 * SUBNAM, INFO, UPLO, TRANS, DIAG, N, KD, NRHS, IMAT
1123 *
1124  9954 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1125  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', N=', i5,
1126  $ ', KD=', i5, ', NRHS=', i4, ', type ', i2 )
1127 *
1128 * SUBNAM, INFO, UPLO, TRANS, DIAG, N, NRHS, IMAT
1129 *
1130  9953 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1131  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', N =', i5,
1132  $ ', NRHS =', i4, ', type ', i2 )
1133 *
1134 * SUBNAM, INFO, UPLO, TRANS, DIAG, NORMIN, N, IMAT
1135 *
1136  9952 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1137  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', NORMIN=''',
1138  $ a1, ''', N =', i5, ', type ', i2 )
1139 *
1140 * SUBNAM, INFO, UPLO, TRANS, DIAG, NORMIN, N, KD, IMAT
1141 *
1142  9951 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1143  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', NORMIN=''',
1144  $ a1, ''', N=', i5, ', KD=', i5, ', type ', i2 )
1145 *
1146 * Unknown type
1147 *
1148  9950 FORMAT( ' *** Error code from ', a, ' =', i5 )
1149 *
1150 * What we do next
1151 *
1152  9949 FORMAT( ' ==> Doing only the condition estimate for this case' )
1153 *
1154  RETURN
1155 *
1156 * End of ALAERH
1157 *
1158  END
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:107
subroutine alaerh(PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU, N5, IMAT, NFAIL, NERRS, NOUT)
ALAERH
Definition: alaerh.f:149
subroutine aladhd(IOUNIT, PATH)
ALADHD
Definition: aladhd.f:92