LAPACK  3.6.1
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 November 2013
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.5.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 * November 2013
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, 'HE' )
493  $ .OR. lsamen( 2, p2, 'HR' ) ) THEN
494 *
495 * xSY: symmetric indefinite matrices
496 * with partial (Bunch-Kaufman) pivoting;
497 * xSR: symmetric indefinite matrices
498 * with rook (bounded Bunch-Kaufman) pivoting;
499 * xHE: Hermitian indefinite matrices
500 * with partial (Bunch-Kaufman) pivoting.
501 * xHR: Hermitian indefinite matrices
502 * with rook (bounded Bunch-Kaufman) pivoting;
503 *
504  uplo = opts( 1: 1 )
505  IF( lsamen( 3, c3, 'TRF' ) ) THEN
506  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
507  WRITE( nout, fmt = 9980 )
508  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
509  $ n5, imat
510  ELSE
511  WRITE( nout, fmt = 9956 )
512  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
513  END IF
514  IF( info.NE.0 )
515  $ WRITE( nout, fmt = 9949 )
516 *
517  ELSE IF( lsamen( 2, c3, 'SV' ) ) THEN
518 *
519  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
520  WRITE( nout, fmt = 9979 )
521  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
522  $ n5, imat
523  ELSE
524  WRITE( nout, fmt = 9955 )
525  $ subnam(1:len_trim( subnam )), info, uplo, n, n5, imat
526  END IF
527 *
528  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
529 *
530  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
531  WRITE( nout, fmt = 9990 )
532  $ subnam(1:len_trim( subnam )), info, infoe,
533  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
534  ELSE
535  WRITE( nout, fmt = 9995 )
536  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
537  $ opts( 2: 2 ), n, n5, imat
538  END IF
539 *
540  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
541  $ lsamen( 3, c3, 'TRI' ) .OR. lsamen( 3, c3, 'CON' ) )
542  $ THEN
543 *
544  WRITE( nout, fmt = 9960 )
545  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
546 *
547  ELSE
548 *
549  WRITE( nout, fmt = 9955 )
550  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
551  END IF
552 *
553  ELSE IF( lsamen( 2, p2, 'PP' ) .OR. lsamen( 2, p2, 'SP' ) .OR.
554  $ lsamen( 2, p2, 'HP' ) ) THEN
555 *
556 * xPP, xHP, or xSP: Symmetric or Hermitian packed matrices
557 *
558  uplo = opts( 1: 1 )
559  IF( lsamen( 3, c3, 'TRF' ) ) THEN
560  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
561  WRITE( nout, fmt = 9983 )
562  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
563  $ imat
564  ELSE
565  WRITE( nout, fmt = 9960 )
566  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
567  END IF
568  IF( info.NE.0 )
569  $ WRITE( nout, fmt = 9949 )
570 *
571  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
572 *
573  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
574  WRITE( nout, fmt = 9979 )
575  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
576  $ n5, imat
577  ELSE
578  WRITE( nout, fmt = 9955 )
579  $ subnam(1:len_trim( subnam )), info, uplo, n, n5, imat
580  END IF
581 *
582  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
583 *
584  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
585  WRITE( nout, fmt = 9990 )
586  $ subnam(1:len_trim( subnam )), info, infoe,
587  $ opts( 1: 1 ), opts( 2: 2 ), n, n5, imat
588  ELSE
589  WRITE( nout, fmt = 9995 )
590  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
591  $ opts( 2: 2 ), n, n5, imat
592  END IF
593 *
594  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
595  $ lsamen( 3, c3, 'TRI' ) .OR. lsamen( 3, c3, 'CON' ) )
596  $ THEN
597 *
598  WRITE( nout, fmt = 9960 )
599  $ subnam(1:len_trim( subnam )), info, uplo, m, imat
600 *
601  ELSE
602 *
603  WRITE( nout, fmt = 9955 )
604  $ subnam(1:len_trim( subnam )), info, uplo, m, n5, imat
605  END IF
606 *
607  ELSE IF( lsamen( 2, p2, 'PB' ) ) THEN
608 *
609 * xPB: Symmetric (Hermitian) positive definite band matrix
610 *
611  uplo = opts( 1: 1 )
612  IF( lsamen( 3, c3, 'TRF' ) ) THEN
613  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
614  WRITE( nout, fmt = 9982 )
615  $ subnam(1:len_trim( subnam )), info, infoe, uplo, m,
616  $ kl, n5, imat
617  ELSE
618  WRITE( nout, fmt = 9958 )
619  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, n5,
620  $ imat
621  END IF
622  IF( info.NE.0 )
623  $ WRITE( nout, fmt = 9949 )
624 *
625  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
626 *
627  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
628  WRITE( nout, fmt = 9981 )
629  $ subnam(1:len_trim( subnam )), info, infoe, uplo, n,
630  $ kl, n5, imat
631  ELSE
632  WRITE( nout, fmt = 9957 )
633  $ subnam(1:len_trim( subnam )), info, uplo, n, kl, n5,
634  $ imat
635  END IF
636 *
637  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
638 *
639  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
640  WRITE( nout, fmt = 9991 )
641  $ subnam(1:len_trim( subnam )), info, infoe,
642  $ opts( 1: 1 ), opts( 2: 2 ), n, kl, n5, imat
643  ELSE
644  WRITE( nout, fmt = 9996 )
645  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
646  $ opts( 2: 2 ), n, kl, n5, imat
647  END IF
648 *
649  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) .OR.
650  $ lsamen( 3, c3, 'CON' ) ) THEN
651 *
652  WRITE( nout, fmt = 9959 )
653  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, imat
654 *
655  ELSE
656 *
657  WRITE( nout, fmt = 9957 )
658  $ subnam(1:len_trim( subnam )), info, uplo, m, kl, n5,
659  $ imat
660  END IF
661 *
662  ELSE IF( lsamen( 2, p2, 'PT' ) ) THEN
663 *
664 * xPT: Positive definite tridiagonal matrices
665 *
666  IF( lsamen( 3, c3, 'TRF' ) ) THEN
667  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
668  WRITE( nout, fmt = 9987 )
669  $ subnam(1:len_trim( subnam )), info, infoe, n, imat
670  ELSE
671  WRITE( nout, fmt = 9973 )
672  $ subnam(1:len_trim( subnam )), info, n, imat
673  END IF
674  IF( info.NE.0 )
675  $ WRITE( nout, fmt = 9949 )
676 *
677  ELSE IF( lsamen( 3, c3, 'SV ' ) ) THEN
678 *
679  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
680  WRITE( nout, fmt = 9984 )
681  $ subnam(1:len_trim( subnam )), info, infoe, n, n5,
682  $ imat
683  ELSE
684  WRITE( nout, fmt = 9970 )
685  $ subnam(1:len_trim( subnam )), info, n, n5, imat
686  END IF
687 *
688  ELSE IF( lsamen( 3, c3, 'SVX' ) ) THEN
689 *
690  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
691  WRITE( nout, fmt = 9994 )
692  $ subnam(1:len_trim( subnam )), info, infoe,
693  $ opts( 1: 1 ), n, n5, imat
694  ELSE
695  WRITE( nout, fmt = 9999 )
696  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), n,
697  $ n5, imat
698  END IF
699 *
700  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
701 *
702  IF( lsame( subnam( 1: 1 ), 'S' ) .OR.
703  $ lsame( subnam( 1: 1 ), 'D' ) ) THEN
704  WRITE( nout, fmt = 9973 )
705  $ subnam(1:len_trim( subnam )), info, m, imat
706  ELSE
707  WRITE( nout, fmt = 9969 )
708  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m,
709  $ imat
710  END IF
711 *
712  ELSE
713 *
714  WRITE( nout, fmt = 9963 )
715  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ), m, n5,
716  $ imat
717  END IF
718 *
719  ELSE IF( lsamen( 2, p2, 'TR' ) ) THEN
720 *
721 * xTR: Triangular matrix
722 *
723  IF( lsamen( 3, c3, 'TRI' ) ) THEN
724  WRITE( nout, fmt = 9961 )
725  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
726  $ opts( 2: 2 ), m, n5, imat
727  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
728  WRITE( nout, fmt = 9967 )
729  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
730  $ opts( 2: 2 ), opts( 3: 3 ), m, imat
731  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATRS' ) ) THEN
732  WRITE( nout, fmt = 9952 )
733  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
734  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, imat
735  ELSE
736  WRITE( nout, fmt = 9953 )
737  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
738  $ opts( 2: 2 ), opts( 3: 3 ), m, n5, imat
739  END IF
740 *
741  ELSE IF( lsamen( 2, p2, 'TP' ) ) THEN
742 *
743 * xTP: Triangular packed matrix
744 *
745  IF( lsamen( 3, c3, 'TRI' ) ) THEN
746  WRITE( nout, fmt = 9962 )
747  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
748  $ opts( 2: 2 ), m, imat
749  ELSE IF( lsamen( 3, c3, 'CON' ) ) THEN
750  WRITE( nout, fmt = 9967 )
751  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
752  $ opts( 2: 2 ), opts( 3: 3 ), m, imat
753  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATPS' ) ) THEN
754  WRITE( nout, fmt = 9952 )
755  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
756  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, imat
757  ELSE
758  WRITE( nout, fmt = 9953 )
759  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
760  $ opts( 2: 2 ), opts( 3: 3 ), m, n5, imat
761  END IF
762 *
763  ELSE IF( lsamen( 2, p2, 'TB' ) ) THEN
764 *
765 * xTB: Triangular band matrix
766 *
767  IF( lsamen( 3, c3, 'CON' ) ) THEN
768  WRITE( nout, fmt = 9966 )
769  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
770  $ opts( 2: 2 ), opts( 3: 3 ), m, kl, imat
771  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATBS' ) ) THEN
772  WRITE( nout, fmt = 9951 )
773  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
774  $ opts( 2: 2 ), opts( 3: 3 ), opts( 4: 4 ), m, kl, imat
775  ELSE
776  WRITE( nout, fmt = 9954 )
777  $ subnam(1:len_trim( subnam )), info, opts( 1: 1 ),
778  $ opts( 2: 2 ), opts( 3: 3 ), m, kl, n5, imat
779  END IF
780 *
781  ELSE IF( lsamen( 2, p2, 'QR' ) ) THEN
782 *
783 * xQR: QR factorization
784 *
785  IF( lsamen( 3, c3, 'QRS' ) ) THEN
786  WRITE( nout, fmt = 9974 )
787  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
788  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
789  WRITE( nout, fmt = 9978 )
790  $ subnam(1:len_trim( subnam )), info, m, n, imat
791  END IF
792 *
793  ELSE IF( lsamen( 2, p2, 'LQ' ) ) THEN
794 *
795 * xLQ: LQ factorization
796 *
797  IF( lsamen( 3, c3, 'LQS' ) ) THEN
798  WRITE( nout, fmt = 9974 )
799  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
800  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
801  WRITE( nout, fmt = 9978 )
802  $ subnam(1:len_trim( subnam )), info, m, n, imat
803  END IF
804 *
805  ELSE IF( lsamen( 2, p2, 'QL' ) ) THEN
806 *
807 * xQL: QL factorization
808 *
809  IF( lsamen( 3, c3, 'QLS' ) ) THEN
810  WRITE( nout, fmt = 9974 )
811  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
812  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
813  WRITE( nout, fmt = 9978 )
814  $ subnam(1:len_trim( subnam )), info, m, n, imat
815  END IF
816 *
817  ELSE IF( lsamen( 2, p2, 'RQ' ) ) THEN
818 *
819 * xRQ: RQ factorization
820 *
821  IF( lsamen( 3, c3, 'RQS' ) ) THEN
822  WRITE( nout, fmt = 9974 )
823  $ subnam(1:len_trim( subnam )), info, m, n, kl, n5, imat
824  ELSE IF( lsamen( 5, subnam( 2: 6 ), 'LATMS' ) ) THEN
825  WRITE( nout, fmt = 9978 )
826  $ subnam(1:len_trim( subnam )), info, m, n, imat
827  END IF
828 *
829  ELSE IF( lsamen( 2, p2, 'LU' ) ) THEN
830 *
831  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
832  WRITE( nout, fmt = 9988 )
833  $ subnam(1:len_trim( subnam )), info, infoe, m, n, n5,
834  $ imat
835  ELSE
836  WRITE( nout, fmt = 9975 )
837  $ subnam(1:len_trim( subnam )), info, m, n, n5, imat
838  END IF
839 *
840  ELSE IF( lsamen( 2, p2, 'CH' ) ) THEN
841 *
842  IF( info.NE.infoe .AND. infoe.NE.0 ) THEN
843  WRITE( nout, fmt = 9985 )
844  $ subnam(1:len_trim( subnam )), info, infoe, m, n5, imat
845  ELSE
846  WRITE( nout, fmt = 9971 )
847  $ subnam(1:len_trim( subnam )), info, m, n5, imat
848  END IF
849 *
850  ELSE
851 *
852 * Print a generic message if the path is unknown.
853 *
854  WRITE( nout, fmt = 9950 )
855  $ subnam(1:len_trim( subnam )), info
856  END IF
857 *
858 * Description of error message (alphabetical, left to right)
859 *
860 * SUBNAM, INFO, FACT, N, NRHS, IMAT
861 *
862  9999 FORMAT( ' *** Error code from ', a, '=', i5, ', FACT=''', a1,
863  $ ''', N=', i5, ', NRHS=', i4, ', type ', i2 )
864 *
865 * SUBNAM, INFO, FACT, TRANS, N, KL, KU, NRHS, IMAT
866 *
867  9998 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
868  $ a1, ''', TRANS=''', a1, ''', N=', i5, ', KL=', i5, ', KU=',
869  $ i5, ', NRHS=', i4, ', type ', i1 )
870 *
871 * SUBNAM, INFO, FACT, TRANS, N, NRHS, IMAT
872 *
873  9997 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
874  $ a1, ''', TRANS=''', a1, ''', N =', i5, ', NRHS =', i4,
875  $ ', type ', i2 )
876 *
877 * SUBNAM, INFO, FACT, UPLO, N, KD, NRHS, IMAT
878 *
879  9996 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
880  $ a1, ''', UPLO=''', a1, ''', N=', i5, ', KD=', i5, ', NRHS=',
881  $ i4, ', type ', i2 )
882 *
883 * SUBNAM, INFO, FACT, UPLO, N, NRHS, IMAT
884 *
885  9995 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> FACT=''',
886  $ a1, ''', UPLO=''', a1, ''', N =', i5, ', NRHS =', i4,
887  $ ', type ', i2 )
888 *
889 * SUBNAM, INFO, INFOE, FACT, N, NRHS, IMAT
890 *
891  9994 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
892  $ i2, / ' ==> FACT=''', a1, ''', N =', i5, ', NRHS =', i4,
893  $ ', type ', i2 )
894 *
895 * SUBNAM, INFO, INFOE, FACT, TRANS, N, KL, KU, NRHS, IMAT
896 *
897  9993 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
898  $ i2, / ' ==> FACT=''', a1, ''', TRANS=''', a1, ''', N=', i5,
899  $ ', KL=', i5, ', KU=', i5, ', NRHS=', i4, ', type ', i1 )
900 *
901 * SUBNAM, INFO, INFOE, FACT, TRANS, N, NRHS, IMAT
902 *
903  9992 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
904  $ i2, / ' ==> FACT=''', a1, ''', TRANS=''', a1, ''', N =', i5,
905  $ ', NRHS =', i4, ', type ', i2 )
906 *
907 * SUBNAM, INFO, INFOE, FACT, UPLO, N, KD, NRHS, IMAT
908 *
909  9991 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
910  $ i2, / ' ==> FACT=''', a1, ''', UPLO=''', a1, ''', N=', i5,
911  $ ', KD=', i5, ', NRHS=', i4, ', type ', i2 )
912 *
913 * SUBNAM, INFO, INFOE, FACT, UPLO, N, NRHS, IMAT
914 *
915  9990 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
916  $ i2, / ' ==> FACT=''', a1, ''', UPLO=''', a1, ''', N =', i5,
917  $ ', NRHS =', i4, ', type ', i2 )
918 *
919 * SUBNAM, INFO, INFOE, M, N, KL, KU, NB, IMAT
920 *
921  9989 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
922  $ i2, / ' ==> M = ', i5, ', N =', i5, ', KL =', i5, ', KU =',
923  $ i5, ', NB =', i4, ', type ', i2 )
924 *
925 * SUBNAM, INFO, INFOE, M, N, NB, IMAT
926 *
927  9988 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
928  $ i2, / ' ==> M =', i5, ', N =', i5, ', NB =', i4, ', type ',
929  $ i2 )
930 *
931 * SUBNAM, INFO, INFOE, N, IMAT
932 *
933  9987 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
934  $ i2, ' for N=', i5, ', type ', i2 )
935 *
936 * SUBNAM, INFO, INFOE, N, KL, KU, NRHS, IMAT
937 *
938  9986 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
939  $ i2, / ' ==> N =', i5, ', KL =', i5, ', KU =', i5,
940  $ ', NRHS =', i4, ', type ', i2 )
941 *
942 * SUBNAM, INFO, INFOE, N, NB, IMAT
943 *
944  9985 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
945  $ i2, / ' ==> N =', i5, ', NB =', i4, ', type ', i2 )
946 *
947 * SUBNAM, INFO, INFOE, N, NRHS, IMAT
948 *
949  9984 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
950  $ i2, / ' ==> N =', i5, ', NRHS =', i4, ', type ', i2 )
951 *
952 * SUBNAM, INFO, INFOE, UPLO, N, IMAT
953 *
954  9983 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
955  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', type ', i2 )
956 *
957 * SUBNAM, INFO, INFOE, UPLO, N, KD, NB, IMAT
958 *
959  9982 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
960  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', KD =', i5,
961  $ ', NB =', i4, ', type ', i2 )
962 *
963 * SUBNAM, INFO, INFOE, UPLO, N, KD, NRHS, IMAT
964 *
965  9981 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
966  $ i2, / ' ==> UPLO=''', a1, ''', N =', i5, ', KD =', i5,
967  $ ', NRHS =', i4, ', type ', i2 )
968 *
969 * SUBNAM, INFO, INFOE, UPLO, N, NB, IMAT
970 *
971  9980 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
972  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', NB =', i4,
973  $ ', type ', i2 )
974 *
975 * SUBNAM, INFO, INFOE, UPLO, N, NRHS, IMAT
976 *
977  9979 FORMAT( ' *** ', a, ' returned with INFO =', i5, ' instead of ',
978  $ i2, / ' ==> UPLO = ''', a1, ''', N =', i5, ', NRHS =', i4,
979  $ ', type ', i2 )
980 *
981 * SUBNAM, INFO, M, N, IMAT
982 *
983  9978 FORMAT( ' *** Error code from ', a, ' =', i5, ' for M =', i5,
984  $ ', N =', i5, ', type ', i2 )
985 *
986 * SUBNAM, INFO, M, N, KL, KU, IMAT
987 *
988  9977 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> M = ', i5,
989  $ ', N =', i5, ', KL =', i5, ', KU =', i5, ', type ', i2 )
990 *
991 * SUBNAM, INFO, M, N, KL, KU, NB, IMAT
992 *
993  9976 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> M = ', i5,
994  $ ', N =', i5, ', KL =', i5, ', KU =', i5, ', NB =', i4,
995  $ ', type ', i2 )
996 *
997 * SUBNAM, INFO, M, N, NB, IMAT
998 *
999  9975 FORMAT( ' *** Error code from ', a, '=', i5, ' for M=', i5,
1000  $ ', N=', i5, ', NB=', i4, ', type ', i2 )
1001 *
1002 * SUBNAM, INFO, M, N, NRHS, NB, IMAT
1003 *
1004  9974 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> M =', i5,
1005  $ ', N =', i5, ', NRHS =', i4, ', NB =', i4, ', type ', i2 )
1006 *
1007 * SUBNAM, INFO, N, IMAT
1008 *
1009  9973 FORMAT( ' *** Error code from ', a, ' =', i5, ' for N =', i5,
1010  $ ', type ', i2 )
1011 *
1012 * SUBNAM, INFO, N, KL, KU, NRHS, IMAT
1013 *
1014  9972 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> N =', i5,
1015  $ ', KL =', i5, ', KU =', i5, ', NRHS =', i4, ', type ', i2 )
1016 *
1017 * SUBNAM, INFO, N, NB, IMAT
1018 *
1019  9971 FORMAT( ' *** Error code from ', a, '=', i5, ' for N=', i5,
1020  $ ', NB=', i4, ', type ', i2 )
1021 *
1022 * SUBNAM, INFO, N, NRHS, IMAT
1023 *
1024  9970 FORMAT( ' *** Error code from ', a, ' =', i5, ' for N =', i5,
1025  $ ', NRHS =', i4, ', type ', i2 )
1026 *
1027 * SUBNAM, INFO, NORM, N, IMAT
1028 *
1029  9969 FORMAT( ' *** Error code from ', a, ' =', i5, ' for NORM = ''',
1030  $ a1, ''', N =', i5, ', type ', i2 )
1031 *
1032 * SUBNAM, INFO, NORM, N, KL, KU, IMAT
1033 *
1034  9968 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM =''',
1035  $ a1, ''', N =', i5, ', KL =', i5, ', KU =', i5, ', type ',
1036  $ i2 )
1037 *
1038 * SUBNAM, INFO, NORM, UPLO, DIAG, N, IMAT
1039 *
1040  9967 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM=''',
1041  $ a1, ''', UPLO =''', a1, ''', DIAG=''', a1, ''', N =', i5,
1042  $ ', type ', i2 )
1043 *
1044 * SUBNAM, INFO, NORM, UPLO, DIAG, N, KD, IMAT
1045 *
1046  9966 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> NORM=''',
1047  $ a1, ''', UPLO =''', a1, ''', DIAG=''', a1, ''', N=', i5,
1048  $ ', KD=', i5, ', type ', i2 )
1049 *
1050 * SUBNAM, INFO, TRANS, M, N, NRHS, NB, IMAT
1051 *
1052  9965 FORMAT( ' *** Error code from ', a, ' =', i5,
1053  $ / ' ==> TRANS = ''', a1, ''', M =', i5, ', N =', i5,
1054  $ ', NRHS =', i4, ', NB =', i4, ', type ', i2 )
1055 *
1056 * SUBNAM, INFO, TRANS, N, KL, KU, NRHS, IMAT
1057 *
1058  9964 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> TRANS=''',
1059  $ a1, ''', N =', i5, ', KL =', i5, ', KU =', i5, ', NRHS =',
1060  $ i4, ', type ', i2 )
1061 *
1062 * SUBNAM, INFO, TRANS, N, NRHS, IMAT
1063 *
1064  9963 FORMAT( ' *** Error code from ', a, ' =', i5,
1065  $ / ' ==> TRANS = ''', a1, ''', N =', i5, ', NRHS =', i4,
1066  $ ', type ', i2 )
1067 *
1068 * SUBNAM, INFO, UPLO, DIAG, N, IMAT
1069 *
1070  9962 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1071  $ a1, ''', DIAG =''', a1, ''', N =', i5, ', type ', i2 )
1072 *
1073 * SUBNAM, INFO, UPLO, DIAG, N, NB, IMAT
1074 *
1075  9961 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1076  $ a1, ''', DIAG =''', a1, ''', N =', i5, ', NB =', i4,
1077  $ ', type ', i2 )
1078 *
1079 * SUBNAM, INFO, UPLO, N, IMAT
1080 *
1081  9960 FORMAT( ' *** Error code from ', a, ' =', i5, ' for UPLO = ''',
1082  $ a1, ''', N =', i5, ', type ', i2 )
1083 *
1084 * SUBNAM, INFO, UPLO, N, KD, IMAT
1085 *
1086  9959 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1087  $ a1, ''', N =', i5, ', KD =', i5, ', type ', i2 )
1088 *
1089 * SUBNAM, INFO, UPLO, N, KD, NB, IMAT
1090 *
1091  9958 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1092  $ a1, ''', N =', i5, ', KD =', i5, ', NB =', i4, ', type ',
1093  $ i2 )
1094 *
1095 * SUBNAM, INFO, UPLO, N, KD, NRHS, IMAT
1096 *
1097  9957 FORMAT( ' *** Error code from ', a, '=', i5, / ' ==> UPLO = ''',
1098  $ a1, ''', N =', i5, ', KD =', i5, ', NRHS =', i4, ', type ',
1099  $ i2 )
1100 *
1101 * SUBNAM, INFO, UPLO, N, NB, IMAT
1102 *
1103  9956 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1104  $ a1, ''', N =', i5, ', NB =', i4, ', type ', i2 )
1105 *
1106 * SUBNAM, INFO, UPLO, N, NRHS, IMAT
1107 *
1108  9955 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO = ''',
1109  $ a1, ''', N =', i5, ', NRHS =', i4, ', type ', i2 )
1110 *
1111 * SUBNAM, INFO, UPLO, TRANS, DIAG, N, KD, NRHS, IMAT
1112 *
1113  9954 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1114  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', N=', i5,
1115  $ ', KD=', i5, ', NRHS=', i4, ', type ', i2 )
1116 *
1117 * SUBNAM, INFO, UPLO, TRANS, DIAG, N, NRHS, IMAT
1118 *
1119  9953 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1120  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', N =', i5,
1121  $ ', NRHS =', i4, ', type ', i2 )
1122 *
1123 * SUBNAM, INFO, UPLO, TRANS, DIAG, NORMIN, N, IMAT
1124 *
1125  9952 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1126  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', NORMIN=''',
1127  $ a1, ''', N =', i5, ', type ', i2 )
1128 *
1129 * SUBNAM, INFO, UPLO, TRANS, DIAG, NORMIN, N, KD, IMAT
1130 *
1131  9951 FORMAT( ' *** Error code from ', a, ' =', i5, / ' ==> UPLO=''',
1132  $ a1, ''', TRANS=''', a1, ''', DIAG=''', a1, ''', NORMIN=''',
1133  $ a1, ''', N=', i5, ', KD=', i5, ', type ', i2 )
1134 *
1135 * Unknown type
1136 *
1137  9950 FORMAT( ' *** Error code from ', a, ' =', i5 )
1138 *
1139 * What we do next
1140 *
1141  9949 FORMAT( ' ==> Doing only the condition estimate for this case' )
1142 *
1143  RETURN
1144 *
1145 * End of ALAERH
1146 *
1147  END
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:95
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:80