LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cerrvx.f
Go to the documentation of this file.
1 *> \brief \b CERRVX
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 CERRVX( 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 *> CERRVX tests the error exits for the COMPLEX driver routines
25 *> for solving linear systems of equations.
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 *> \date November 2013
52 *
53 *> \ingroup complex_lin
54 *
55 * =====================================================================
56  SUBROUTINE cerrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.5.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * November 2013
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 PATH
65  INTEGER NUNIT
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER NMAX
72  parameter ( nmax = 4 )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER EQ
76  CHARACTER*2 C2
77  INTEGER I, INFO, J
78  REAL RCOND
79 * ..
80 * .. Local Arrays ..
81  INTEGER IP( nmax )
82  REAL C( nmax ), R( nmax ), R1( nmax ), R2( nmax ),
83  $ rf( nmax ), rw( nmax )
84  COMPLEX A( nmax, nmax ), AF( nmax, nmax ), B( nmax ),
85  $ w( 2*nmax ), x( nmax )
86 * ..
87 * .. External Functions ..
88  LOGICAL LSAMEN
89  EXTERNAL lsamen
90 * ..
91 * .. External Subroutines ..
92  EXTERNAL cgbsv, cgbsvx, cgesv, cgesvx, cgtsv, cgtsvx,
97 * ..
98 * .. Scalars in Common ..
99  LOGICAL LERR, OK
100  CHARACTER*32 SRNAMT
101  INTEGER INFOT, NOUT
102 * ..
103 * .. Common blocks ..
104  COMMON / infoc / infot, nout, ok, lerr
105  COMMON / srnamc / srnamt
106 * ..
107 * .. Intrinsic Functions ..
108  INTRINSIC cmplx, real
109 * ..
110 * .. Executable Statements ..
111 *
112  nout = nunit
113  WRITE( nout, fmt = * )
114  c2 = path( 2: 3 )
115 *
116 * Set the variables to innocuous values.
117 *
118  DO 20 j = 1, nmax
119  DO 10 i = 1, nmax
120  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
121  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
122  10 CONTINUE
123  b( j ) = 0.
124  r1( j ) = 0.
125  r2( j ) = 0.
126  w( j ) = 0.
127  x( j ) = 0.
128  c( j ) = 0.
129  r( j ) = 0.
130  ip( j ) = j
131  20 CONTINUE
132  eq = ' '
133  ok = .true.
134 *
135  IF( lsamen( 2, c2, 'GE' ) ) THEN
136 *
137 * CGESV
138 *
139  srnamt = 'CGESV '
140  infot = 1
141  CALL cgesv( -1, 0, a, 1, ip, b, 1, info )
142  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
143  infot = 2
144  CALL cgesv( 0, -1, a, 1, ip, b, 1, info )
145  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
146  infot = 4
147  CALL cgesv( 2, 1, a, 1, ip, b, 2, info )
148  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
149  infot = 7
150  CALL cgesv( 2, 1, a, 2, ip, b, 1, info )
151  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
152 *
153 * CGESVX
154 *
155  srnamt = 'CGESVX'
156  infot = 1
157  CALL cgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
158  $ x, 1, rcond, r1, r2, w, rw, info )
159  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
160  infot = 2
161  CALL cgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
162  $ x, 1, rcond, r1, r2, w, rw, info )
163  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
164  infot = 3
165  CALL cgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
166  $ x, 1, rcond, r1, r2, w, rw, info )
167  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
168  infot = 4
169  CALL cgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
170  $ x, 1, rcond, r1, r2, w, rw, info )
171  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
172  infot = 6
173  CALL cgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
174  $ x, 2, rcond, r1, r2, w, rw, info )
175  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
176  infot = 8
177  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
178  $ x, 2, rcond, r1, r2, w, rw, info )
179  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
180  infot = 10
181  eq = '/'
182  CALL cgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
183  $ x, 1, rcond, r1, r2, w, rw, info )
184  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
185  infot = 11
186  eq = 'R'
187  CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
188  $ x, 1, rcond, r1, r2, w, rw, info )
189  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
190  infot = 12
191  eq = 'C'
192  CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
193  $ x, 1, rcond, r1, r2, w, rw, info )
194  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
195  infot = 14
196  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
197  $ x, 2, rcond, r1, r2, w, rw, info )
198  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
199  infot = 16
200  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
201  $ x, 1, rcond, r1, r2, w, rw, info )
202  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
203 *
204  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
205 *
206 * CGBSV
207 *
208  srnamt = 'CGBSV '
209  infot = 1
210  CALL cgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
211  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
212  infot = 2
213  CALL cgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
214  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
215  infot = 3
216  CALL cgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
217  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
218  infot = 4
219  CALL cgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
220  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
221  infot = 6
222  CALL cgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
223  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
224  infot = 9
225  CALL cgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
226  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
227 *
228 * CGBSVX
229 *
230  srnamt = 'CGBSVX'
231  infot = 1
232  CALL cgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
233  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
234  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
235  infot = 2
236  CALL cgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
237  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
238  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
239  infot = 3
240  CALL cgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
241  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
242  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
243  infot = 4
244  CALL cgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
245  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
246  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
247  infot = 5
248  CALL cgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
249  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
250  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
251  infot = 6
252  CALL cgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
253  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
254  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
255  infot = 8
256  CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
257  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
258  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
259  infot = 10
260  CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
261  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
262  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
263  infot = 12
264  eq = '/'
265  CALL cgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
266  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
267  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
268  infot = 13
269  eq = 'R'
270  CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
271  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
272  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
273  infot = 14
274  eq = 'C'
275  CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
276  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
277  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
278  infot = 16
279  CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
280  $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
281  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
282  infot = 18
283  CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
284  $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
285  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
286 *
287  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
288 *
289 * CGTSV
290 *
291  srnamt = 'CGTSV '
292  infot = 1
293  CALL cgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
294  $ info )
295  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
296  infot = 2
297  CALL cgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
298  $ info )
299  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
300  infot = 7
301  CALL cgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
302  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
303 *
304 * CGTSVX
305 *
306  srnamt = 'CGTSVX'
307  infot = 1
308  CALL cgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
309  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
310  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
311  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
312  infot = 2
313  CALL cgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
314  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
315  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
316  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
317  infot = 3
318  CALL cgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
319  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
320  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
321  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
322  infot = 4
323  CALL cgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
324  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
325  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
326  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
327  infot = 14
328  CALL cgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
329  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
330  $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
331  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
332  infot = 16
333  CALL cgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
334  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
335  $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
336  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
337 *
338  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
339 *
340 * CPOSV
341 *
342  srnamt = 'CPOSV '
343  infot = 1
344  CALL cposv( '/', 0, 0, a, 1, b, 1, info )
345  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
346  infot = 2
347  CALL cposv( 'U', -1, 0, a, 1, b, 1, info )
348  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
349  infot = 3
350  CALL cposv( 'U', 0, -1, a, 1, b, 1, info )
351  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
352  infot = 5
353  CALL cposv( 'U', 2, 0, a, 1, b, 2, info )
354  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
355  infot = 7
356  CALL cposv( 'U', 2, 0, a, 2, b, 1, info )
357  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
358 *
359 * CPOSVX
360 *
361  srnamt = 'CPOSVX'
362  infot = 1
363  CALL cposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
364  $ rcond, r1, r2, w, rw, info )
365  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
366  infot = 2
367  CALL cposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
368  $ rcond, r1, r2, w, rw, info )
369  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
370  infot = 3
371  CALL cposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
372  $ rcond, r1, r2, w, rw, info )
373  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
374  infot = 4
375  CALL cposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
376  $ rcond, r1, r2, w, rw, info )
377  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
378  infot = 6
379  CALL cposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
380  $ rcond, r1, r2, w, rw, info )
381  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
382  infot = 8
383  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
384  $ rcond, r1, r2, w, rw, info )
385  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
386  infot = 9
387  eq = '/'
388  CALL cposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
389  $ rcond, r1, r2, w, rw, info )
390  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
391  infot = 10
392  eq = 'Y'
393  CALL cposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
394  $ rcond, r1, r2, w, rw, info )
395  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
396  infot = 12
397  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
398  $ rcond, r1, r2, w, rw, info )
399  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
400  infot = 14
401  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
402  $ rcond, r1, r2, w, rw, info )
403  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
404 *
405  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
406 *
407 * CPPSV
408 *
409  srnamt = 'CPPSV '
410  infot = 1
411  CALL cppsv( '/', 0, 0, a, b, 1, info )
412  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
413  infot = 2
414  CALL cppsv( 'U', -1, 0, a, b, 1, info )
415  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
416  infot = 3
417  CALL cppsv( 'U', 0, -1, a, b, 1, info )
418  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
419  infot = 6
420  CALL cppsv( 'U', 2, 0, a, b, 1, info )
421  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
422 *
423 * CPPSVX
424 *
425  srnamt = 'CPPSVX'
426  infot = 1
427  CALL cppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
428  $ r1, r2, w, rw, info )
429  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
430  infot = 2
431  CALL cppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
432  $ r1, r2, w, rw, info )
433  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
434  infot = 3
435  CALL cppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
436  $ r1, r2, w, rw, info )
437  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
438  infot = 4
439  CALL cppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
440  $ r1, r2, w, rw, info )
441  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
442  infot = 7
443  eq = '/'
444  CALL cppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
445  $ r1, r2, w, rw, info )
446  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
447  infot = 8
448  eq = 'Y'
449  CALL cppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
450  $ r1, r2, w, rw, info )
451  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
452  infot = 10
453  CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
454  $ r1, r2, w, rw, info )
455  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
456  infot = 12
457  CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
458  $ r1, r2, w, rw, info )
459  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
460 *
461  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
462 *
463 * CPBSV
464 *
465  srnamt = 'CPBSV '
466  infot = 1
467  CALL cpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
468  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
469  infot = 2
470  CALL cpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
471  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
472  infot = 3
473  CALL cpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
474  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
475  infot = 4
476  CALL cpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
477  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
478  infot = 6
479  CALL cpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
480  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
481  infot = 8
482  CALL cpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
483  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
484 *
485 * CPBSVX
486 *
487  srnamt = 'CPBSVX'
488  infot = 1
489  CALL cpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
490  $ rcond, r1, r2, w, rw, info )
491  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
492  infot = 2
493  CALL cpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
494  $ rcond, r1, r2, w, rw, info )
495  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
496  infot = 3
497  CALL cpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
498  $ 1, rcond, r1, r2, w, rw, info )
499  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
500  infot = 4
501  CALL cpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
502  $ 1, rcond, r1, r2, w, rw, info )
503  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
504  infot = 5
505  CALL cpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
506  $ 1, rcond, r1, r2, w, rw, info )
507  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
508  infot = 7
509  CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
510  $ rcond, r1, r2, w, rw, info )
511  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
512  infot = 9
513  CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
514  $ rcond, r1, r2, w, rw, info )
515  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
516  infot = 10
517  eq = '/'
518  CALL cpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
519  $ rcond, r1, r2, w, rw, info )
520  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
521  infot = 11
522  eq = 'Y'
523  CALL cpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
524  $ rcond, r1, r2, w, rw, info )
525  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
526  infot = 13
527  CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
528  $ rcond, r1, r2, w, rw, info )
529  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
530  infot = 15
531  CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
532  $ rcond, r1, r2, w, rw, info )
533  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
534 *
535  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
536 *
537 * CPTSV
538 *
539  srnamt = 'CPTSV '
540  infot = 1
541  CALL cptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
542  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
543  infot = 2
544  CALL cptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
545  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
546  infot = 6
547  CALL cptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
548  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
549 *
550 * CPTSVX
551 *
552  srnamt = 'CPTSVX'
553  infot = 1
554  CALL cptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
555  $ 1, rcond, r1, r2, w, rw, info )
556  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
557  infot = 2
558  CALL cptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
559  $ 1, rcond, r1, r2, w, rw, info )
560  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
561  infot = 3
562  CALL cptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
563  $ 1, rcond, r1, r2, w, rw, info )
564  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
565  infot = 9
566  CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
567  $ 2, rcond, r1, r2, w, rw, info )
568  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
569  infot = 11
570  CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
571  $ 1, rcond, r1, r2, w, rw, info )
572  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
573 *
574  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
575 *
576 * CHESV
577 *
578  srnamt = 'CHESV '
579  infot = 1
580  CALL chesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
581  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
582  infot = 2
583  CALL chesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
584  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
585  infot = 3
586  CALL chesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
587  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
588  infot = 5
589  CALL chesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
590  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
591  infot = 8
592  CALL chesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
593  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
594 *
595 * CHESVX
596 *
597  srnamt = 'CHESVX'
598  infot = 1
599  CALL chesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
600  $ rcond, r1, r2, w, 1, rw, info )
601  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
602  infot = 2
603  CALL chesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
604  $ rcond, r1, r2, w, 1, rw, info )
605  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
606  infot = 3
607  CALL chesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
608  $ rcond, r1, r2, w, 1, rw, info )
609  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
610  infot = 4
611  CALL chesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
612  $ rcond, r1, r2, w, 1, rw, info )
613  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
614  infot = 6
615  CALL chesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
616  $ rcond, r1, r2, w, 4, rw, info )
617  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
618  infot = 8
619  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
620  $ rcond, r1, r2, w, 4, rw, info )
621  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
622  infot = 11
623  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
624  $ rcond, r1, r2, w, 4, rw, info )
625  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
626  infot = 13
627  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
628  $ rcond, r1, r2, w, 4, rw, info )
629  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
630  infot = 18
631  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
632  $ rcond, r1, r2, w, 3, rw, info )
633  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
634 *
635  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
636 *
637 * CHESV_ROOK
638 *
639  srnamt = 'CHESV_ROOK'
640  infot = 1
641  CALL chesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
642  CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
643  infot = 2
644  CALL chesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
645  CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
646  infot = 3
647  CALL chesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
648  CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
649  infot = 8
650  CALL chesv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
651  CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
652 *
653  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
654 *
655 * CHPSV
656 *
657  srnamt = 'CHPSV '
658  infot = 1
659  CALL chpsv( '/', 0, 0, a, ip, b, 1, info )
660  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
661  infot = 2
662  CALL chpsv( 'U', -1, 0, a, ip, b, 1, info )
663  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
664  infot = 3
665  CALL chpsv( 'U', 0, -1, a, ip, b, 1, info )
666  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
667  infot = 7
668  CALL chpsv( 'U', 2, 0, a, ip, b, 1, info )
669  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
670 *
671 * CHPSVX
672 *
673  srnamt = 'CHPSVX'
674  infot = 1
675  CALL chpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
676  $ r2, w, rw, info )
677  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
678  infot = 2
679  CALL chpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
680  $ r2, w, rw, info )
681  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
682  infot = 3
683  CALL chpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
684  $ r2, w, rw, info )
685  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
686  infot = 4
687  CALL chpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
688  $ r2, w, rw, info )
689  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
690  infot = 9
691  CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
692  $ r2, w, rw, info )
693  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
694  infot = 11
695  CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
696  $ r2, w, rw, info )
697  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
698 *
699  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
700 *
701 * CSYSV
702 *
703  srnamt = 'CSYSV '
704  infot = 1
705  CALL csysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
706  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
707  infot = 2
708  CALL csysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
709  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
710  infot = 3
711  CALL csysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
712  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
713  infot = 8
714  CALL csysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
715  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
716 *
717 * CSYSVX
718 *
719  srnamt = 'CSYSVX'
720  infot = 1
721  CALL csysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
722  $ rcond, r1, r2, w, 1, rw, info )
723  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
724  infot = 2
725  CALL csysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
726  $ rcond, r1, r2, w, 1, rw, info )
727  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
728  infot = 3
729  CALL csysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
730  $ rcond, r1, r2, w, 1, rw, info )
731  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
732  infot = 4
733  CALL csysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
734  $ rcond, r1, r2, w, 1, rw, info )
735  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
736  infot = 6
737  CALL csysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
738  $ rcond, r1, r2, w, 4, rw, info )
739  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
740  infot = 8
741  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
742  $ rcond, r1, r2, w, 4, rw, info )
743  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
744  infot = 11
745  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
746  $ rcond, r1, r2, w, 4, rw, info )
747  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
748  infot = 13
749  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
750  $ rcond, r1, r2, w, 4, rw, info )
751  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
752  infot = 18
753  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
754  $ rcond, r1, r2, w, 3, rw, info )
755  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
756 *
757  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
758 *
759 * CSYSV_ROOK
760 *
761  srnamt = 'CSYSV_ROOK'
762  infot = 1
763  CALL csysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
764  CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
765  infot = 2
766  CALL csysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
767  CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
768  infot = 3
769  CALL csysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
770  CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
771  infot = 8
772  CALL csysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
773  CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
774 *
775  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
776 *
777 * CSPSV
778 *
779  srnamt = 'CSPSV '
780  infot = 1
781  CALL cspsv( '/', 0, 0, a, ip, b, 1, info )
782  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
783  infot = 2
784  CALL cspsv( 'U', -1, 0, a, ip, b, 1, info )
785  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
786  infot = 3
787  CALL cspsv( 'U', 0, -1, a, ip, b, 1, info )
788  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
789  infot = 7
790  CALL cspsv( 'U', 2, 0, a, ip, b, 1, info )
791  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
792 *
793 * CSPSVX
794 *
795  srnamt = 'CSPSVX'
796  infot = 1
797  CALL cspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
798  $ r2, w, rw, info )
799  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
800  infot = 2
801  CALL cspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
802  $ r2, w, rw, info )
803  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
804  infot = 3
805  CALL cspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
806  $ r2, w, rw, info )
807  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
808  infot = 4
809  CALL cspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
810  $ r2, w, rw, info )
811  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
812  infot = 9
813  CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
814  $ r2, w, rw, info )
815  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
816  infot = 11
817  CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
818  $ r2, w, rw, info )
819  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
820  END IF
821 *
822 * Print a summary line.
823 *
824  IF( ok ) THEN
825  WRITE( nout, fmt = 9999 )path
826  ELSE
827  WRITE( nout, fmt = 9998 )path
828  END IF
829 *
830  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
831  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
832  $ 'exits ***' )
833 *
834  RETURN
835 *
836 * End of CERRVX
837 *
838  END
subroutine chpsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
CHPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: chpsv.f:164
subroutine cgtsv(N, NRHS, DL, D, DU, B, LDB, INFO)
CGTSV computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: cgtsv.f:126
subroutine cgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
CGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver) ...
Definition: cgbsv.f:164
subroutine cspsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
CSPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cspsv.f:164
subroutine cerrvx(PATH, NUNIT)
CERRVX
Definition: cerrvx.f:57
subroutine chesv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CHESV computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: chesv.f:173
subroutine chesvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
CHESVX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: chesvx.f:287
subroutine cgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CGTSVX computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: cgtsvx.f:296
subroutine cptsv(N, NRHS, D, E, B, LDB, INFO)
CPTSV computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: cptsv.f:117
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine csysv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: csysv_rook.f:206
subroutine cspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cspsvx.f:279
subroutine cgesvx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CGESVX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: cgesvx.f:352
subroutine cppsvx(FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cppsvx.f:313
subroutine cgbsvx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CGBSVX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: cgbsvx.f:372
subroutine cpbsv(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
CPBSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cpbsv.f:166
subroutine csysvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
CSYSVX computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: csysvx.f:287
subroutine cpbsvx(FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cpbsvx.f:344
subroutine cposvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CPOSVX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: cposvx.f:308
subroutine csysv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CSYSV computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: csysv.f:173
subroutine cposv(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
CPOSV computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: cposv.f:132
subroutine cptsvx(FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CPTSVX computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: cptsvx.f:236
subroutine cgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CGESV computes the solution to system of linear equations A * X = B for GE matrices (simple driver) ...
Definition: cgesv.f:124
subroutine cppsv(UPLO, N, NRHS, AP, B, LDB, INFO)
CPPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: cppsv.f:146
subroutine chesv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
Definition: chesv_rook.f:207
subroutine chpsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
CHPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: chpsvx.f:279