LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
derrvx.f
Go to the documentation of this file.
1 *> \brief \b DERRVX
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 DERRVX( 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 *> DERRVX tests the error exits for the DOUBLE PRECISION 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 2017
52 *
53 *> \ingroup double_lin
54 *
55 * =====================================================================
56  SUBROUTINE derrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.8.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 2017
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  DOUBLE PRECISION RCOND
79 * ..
80 * .. Local Arrays ..
81  INTEGER IP( NMAX ), IW( NMAX )
82  DOUBLE PRECISION A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
83  $ C( NMAX ), E( NMAX ), R( NMAX ), R1( NMAX ),
84  $ R2( NMAX ), W( 2*NMAX ), X( NMAX )
85 * ..
86 * .. External Functions ..
87  LOGICAL LSAMEN
88  EXTERNAL lsamen
89 * ..
90 * .. External Subroutines ..
91  EXTERNAL chkxer, dgbsv, dgbsvx, dgesv, dgesvx, dgtsv,
96 * ..
97 * .. Scalars in Common ..
98  LOGICAL LERR, OK
99  CHARACTER*32 SRNAMT
100  INTEGER INFOT, NOUT
101 * ..
102 * .. Common blocks ..
103  COMMON / infoc / infot, nout, ok, lerr
104  COMMON / srnamc / srnamt
105 * ..
106 * .. Intrinsic Functions ..
107  INTRINSIC dble
108 * ..
109 * .. Executable Statements ..
110 *
111  nout = nunit
112  WRITE( nout, fmt = * )
113  c2 = path( 2: 3 )
114 *
115 * Set the variables to innocuous values.
116 *
117  DO 20 j = 1, nmax
118  DO 10 i = 1, nmax
119  a( i, j ) = 1.d0 / dble( i+j )
120  af( i, j ) = 1.d0 / dble( i+j )
121  10 CONTINUE
122  b( j ) = 0.d+0
123  e( j ) = 0.d+0
124  r1( j ) = 0.d+0
125  r2( j ) = 0.d+0
126  w( j ) = 0.d+0
127  x( j ) = 0.d+0
128  c( j ) = 0.d+0
129  r( j ) = 0.d+0
130  ip( j ) = j
131  20 CONTINUE
132  eq = ' '
133  ok = .true.
134 *
135  IF( lsamen( 2, c2, 'GE' ) ) THEN
136 *
137 * DGESV
138 *
139  srnamt = 'DGESV '
140  infot = 1
141  CALL dgesv( -1, 0, a, 1, ip, b, 1, info )
142  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
143  infot = 2
144  CALL dgesv( 0, -1, a, 1, ip, b, 1, info )
145  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
146  infot = 4
147  CALL dgesv( 2, 1, a, 1, ip, b, 2, info )
148  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
149  infot = 7
150  CALL dgesv( 2, 1, a, 2, ip, b, 1, info )
151  CALL chkxer( 'DGESV ', infot, nout, lerr, ok )
152 *
153 * DGESVX
154 *
155  srnamt = 'DGESVX'
156  infot = 1
157  CALL dgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
158  $ x, 1, rcond, r1, r2, w, iw, info )
159  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
160  infot = 2
161  CALL dgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
162  $ x, 1, rcond, r1, r2, w, iw, info )
163  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
164  infot = 3
165  CALL dgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
166  $ x, 1, rcond, r1, r2, w, iw, info )
167  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
168  infot = 4
169  CALL dgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
170  $ x, 1, rcond, r1, r2, w, iw, info )
171  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
172  infot = 6
173  CALL dgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
174  $ x, 2, rcond, r1, r2, w, iw, info )
175  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
176  infot = 8
177  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
178  $ x, 2, rcond, r1, r2, w, iw, info )
179  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
180  infot = 10
181  eq = '/'
182  CALL dgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
183  $ x, 1, rcond, r1, r2, w, iw, info )
184  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
185  infot = 11
186  eq = 'R'
187  CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
188  $ x, 1, rcond, r1, r2, w, iw, info )
189  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
190  infot = 12
191  eq = 'C'
192  CALL dgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
193  $ x, 1, rcond, r1, r2, w, iw, info )
194  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
195  infot = 14
196  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
197  $ x, 2, rcond, r1, r2, w, iw, info )
198  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
199  infot = 16
200  CALL dgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
201  $ x, 1, rcond, r1, r2, w, iw, info )
202  CALL chkxer( 'DGESVX', infot, nout, lerr, ok )
203 *
204  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
205 *
206 * DGBSV
207 *
208  srnamt = 'DGBSV '
209  infot = 1
210  CALL dgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
211  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
212  infot = 2
213  CALL dgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
214  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
215  infot = 3
216  CALL dgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
217  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
218  infot = 4
219  CALL dgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
220  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
221  infot = 6
222  CALL dgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
223  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
224  infot = 9
225  CALL dgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
226  CALL chkxer( 'DGBSV ', infot, nout, lerr, ok )
227 *
228 * DGBSVX
229 *
230  srnamt = 'DGBSVX'
231  infot = 1
232  CALL dgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
233  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
234  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
235  infot = 2
236  CALL dgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
237  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
238  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
239  infot = 3
240  CALL dgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
241  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
242  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
243  infot = 4
244  CALL dgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
245  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
246  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
247  infot = 5
248  CALL dgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
249  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
250  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
251  infot = 6
252  CALL dgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
253  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
254  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
255  infot = 8
256  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
257  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
258  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
259  infot = 10
260  CALL dgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
261  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
262  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
263  infot = 12
264  eq = '/'
265  CALL dgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
266  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
267  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
268  infot = 13
269  eq = 'R'
270  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
271  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
272  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
273  infot = 14
274  eq = 'C'
275  CALL dgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
276  $ b, 1, x, 1, rcond, r1, r2, w, iw, info )
277  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
278  infot = 16
279  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
280  $ b, 1, x, 2, rcond, r1, r2, w, iw, info )
281  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
282  infot = 18
283  CALL dgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
284  $ b, 2, x, 1, rcond, r1, r2, w, iw, info )
285  CALL chkxer( 'DGBSVX', infot, nout, lerr, ok )
286 *
287  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
288 *
289 * DGTSV
290 *
291  srnamt = 'DGTSV '
292  infot = 1
293  CALL dgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
294  $ info )
295  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
296  infot = 2
297  CALL dgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
298  $ info )
299  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
300  infot = 7
301  CALL dgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
302  CALL chkxer( 'DGTSV ', infot, nout, lerr, ok )
303 *
304 * DGTSVX
305 *
306  srnamt = 'DGTSVX'
307  infot = 1
308  CALL dgtsvx( '/', '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, iw, info )
311  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
312  infot = 2
313  CALL dgtsvx( '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, iw, info )
316  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
317  infot = 3
318  CALL dgtsvx( '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, iw, info )
321  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
322  infot = 4
323  CALL dgtsvx( '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, iw, info )
326  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
327  infot = 14
328  CALL dgtsvx( '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, iw, info )
331  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
332  infot = 16
333  CALL dgtsvx( '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, iw, info )
336  CALL chkxer( 'DGTSVX', infot, nout, lerr, ok )
337 *
338  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
339 *
340 * DPOSV
341 *
342  srnamt = 'DPOSV '
343  infot = 1
344  CALL dposv( '/', 0, 0, a, 1, b, 1, info )
345  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
346  infot = 2
347  CALL dposv( 'U', -1, 0, a, 1, b, 1, info )
348  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
349  infot = 3
350  CALL dposv( 'U', 0, -1, a, 1, b, 1, info )
351  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
352  infot = 5
353  CALL dposv( 'U', 2, 0, a, 1, b, 2, info )
354  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
355  infot = 7
356  CALL dposv( 'U', 2, 0, a, 2, b, 1, info )
357  CALL chkxer( 'DPOSV ', infot, nout, lerr, ok )
358 *
359 * DPOSVX
360 *
361  srnamt = 'DPOSVX'
362  infot = 1
363  CALL dposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
364  $ rcond, r1, r2, w, iw, info )
365  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
366  infot = 2
367  CALL dposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
368  $ rcond, r1, r2, w, iw, info )
369  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
370  infot = 3
371  CALL dposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
372  $ rcond, r1, r2, w, iw, info )
373  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
374  infot = 4
375  CALL dposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
376  $ rcond, r1, r2, w, iw, info )
377  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
378  infot = 6
379  CALL dposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
380  $ rcond, r1, r2, w, iw, info )
381  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
382  infot = 8
383  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
384  $ rcond, r1, r2, w, iw, info )
385  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
386  infot = 9
387  eq = '/'
388  CALL dposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
389  $ rcond, r1, r2, w, iw, info )
390  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
391  infot = 10
392  eq = 'Y'
393  CALL dposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
394  $ rcond, r1, r2, w, iw, info )
395  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
396  infot = 12
397  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
398  $ rcond, r1, r2, w, iw, info )
399  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
400  infot = 14
401  CALL dposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
402  $ rcond, r1, r2, w, iw, info )
403  CALL chkxer( 'DPOSVX', infot, nout, lerr, ok )
404 *
405  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
406 *
407 * DPPSV
408 *
409  srnamt = 'DPPSV '
410  infot = 1
411  CALL dppsv( '/', 0, 0, a, b, 1, info )
412  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
413  infot = 2
414  CALL dppsv( 'U', -1, 0, a, b, 1, info )
415  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
416  infot = 3
417  CALL dppsv( 'U', 0, -1, a, b, 1, info )
418  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
419  infot = 6
420  CALL dppsv( 'U', 2, 0, a, b, 1, info )
421  CALL chkxer( 'DPPSV ', infot, nout, lerr, ok )
422 *
423 * DPPSVX
424 *
425  srnamt = 'DPPSVX'
426  infot = 1
427  CALL dppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
428  $ r1, r2, w, iw, info )
429  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
430  infot = 2
431  CALL dppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
432  $ r1, r2, w, iw, info )
433  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
434  infot = 3
435  CALL dppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
436  $ r1, r2, w, iw, info )
437  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
438  infot = 4
439  CALL dppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
440  $ r1, r2, w, iw, info )
441  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
442  infot = 7
443  eq = '/'
444  CALL dppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
445  $ r1, r2, w, iw, info )
446  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
447  infot = 8
448  eq = 'Y'
449  CALL dppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
450  $ r1, r2, w, iw, info )
451  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
452  infot = 10
453  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
454  $ r1, r2, w, iw, info )
455  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
456  infot = 12
457  CALL dppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
458  $ r1, r2, w, iw, info )
459  CALL chkxer( 'DPPSVX', infot, nout, lerr, ok )
460 *
461  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
462 *
463 * DPBSV
464 *
465  srnamt = 'DPBSV '
466  infot = 1
467  CALL dpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
468  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
469  infot = 2
470  CALL dpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
471  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
472  infot = 3
473  CALL dpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
474  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
475  infot = 4
476  CALL dpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
477  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
478  infot = 6
479  CALL dpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
480  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
481  infot = 8
482  CALL dpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
483  CALL chkxer( 'DPBSV ', infot, nout, lerr, ok )
484 *
485 * DPBSVX
486 *
487  srnamt = 'DPBSVX'
488  infot = 1
489  CALL dpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
490  $ rcond, r1, r2, w, iw, info )
491  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
492  infot = 2
493  CALL dpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
494  $ rcond, r1, r2, w, iw, info )
495  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
496  infot = 3
497  CALL dpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
498  $ 1, rcond, r1, r2, w, iw, info )
499  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
500  infot = 4
501  CALL dpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
502  $ 1, rcond, r1, r2, w, iw, info )
503  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
504  infot = 5
505  CALL dpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
506  $ 1, rcond, r1, r2, w, iw, info )
507  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
508  infot = 7
509  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
510  $ rcond, r1, r2, w, iw, info )
511  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
512  infot = 9
513  CALL dpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
514  $ rcond, r1, r2, w, iw, info )
515  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
516  infot = 10
517  eq = '/'
518  CALL dpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
519  $ rcond, r1, r2, w, iw, info )
520  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
521  infot = 11
522  eq = 'Y'
523  CALL dpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
524  $ rcond, r1, r2, w, iw, info )
525  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
526  infot = 13
527  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
528  $ rcond, r1, r2, w, iw, info )
529  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
530  infot = 15
531  CALL dpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
532  $ rcond, r1, r2, w, iw, info )
533  CALL chkxer( 'DPBSVX', infot, nout, lerr, ok )
534 *
535  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
536 *
537 * DPTSV
538 *
539  srnamt = 'DPTSV '
540  infot = 1
541  CALL dptsv( -1, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
542  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
543  infot = 2
544  CALL dptsv( 0, -1, a( 1, 1 ), a( 1, 2 ), b, 1, info )
545  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
546  infot = 6
547  CALL dptsv( 2, 0, a( 1, 1 ), a( 1, 2 ), b, 1, info )
548  CALL chkxer( 'DPTSV ', infot, nout, lerr, ok )
549 *
550 * DPTSVX
551 *
552  srnamt = 'DPTSVX'
553  infot = 1
554  CALL dptsvx( '/', 0, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
555  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
556  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
557  infot = 2
558  CALL dptsvx( 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
559  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
560  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
561  infot = 3
562  CALL dptsvx( 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
563  $ af( 1, 2 ), b, 1, x, 1, rcond, r1, r2, w, info )
564  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
565  infot = 9
566  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
567  $ af( 1, 2 ), b, 1, x, 2, rcond, r1, r2, w, info )
568  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
569  infot = 11
570  CALL dptsvx( 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), af( 1, 1 ),
571  $ af( 1, 2 ), b, 2, x, 1, rcond, r1, r2, w, info )
572  CALL chkxer( 'DPTSVX', infot, nout, lerr, ok )
573 *
574  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
575 *
576 * DSYSV
577 *
578  srnamt = 'DSYSV '
579  infot = 1
580  CALL dsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
581  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
582  infot = 2
583  CALL dsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
584  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
585  infot = 3
586  CALL dsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
587  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
588  infot = 5
589  CALL dsysv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
590  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
591  infot = 8
592  CALL dsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
593  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
594  infot = 10
595  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
596  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
597  infot = 10
598  CALL dsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
599  CALL chkxer( 'DSYSV ', infot, nout, lerr, ok )
600 *
601 * DSYSVX
602 *
603  srnamt = 'DSYSVX'
604  infot = 1
605  CALL dsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
606  $ rcond, r1, r2, w, 1, iw, info )
607  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
608  infot = 2
609  CALL dsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
610  $ rcond, r1, r2, w, 1, iw, info )
611  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
612  infot = 3
613  CALL dsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
614  $ rcond, r1, r2, w, 1, iw, info )
615  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
616  infot = 4
617  CALL dsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
618  $ rcond, r1, r2, w, 1, iw, info )
619  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
620  infot = 6
621  CALL dsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
622  $ rcond, r1, r2, w, 4, iw, info )
623  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
624  infot = 8
625  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
626  $ rcond, r1, r2, w, 4, iw, info )
627  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
628  infot = 11
629  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
630  $ rcond, r1, r2, w, 4, iw, info )
631  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
632  infot = 13
633  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
634  $ rcond, r1, r2, w, 4, iw, info )
635  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
636  infot = 18
637  CALL dsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
638  $ rcond, r1, r2, w, 3, iw, info )
639  CALL chkxer( 'DSYSVX', infot, nout, lerr, ok )
640 *
641  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
642 *
643 * DSYSV_ROOK
644 *
645  srnamt = 'DSYSV_ROOK'
646  infot = 1
647  CALL dsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
648  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
649  infot = 2
650  CALL dsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
651  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
652  infot = 3
653  CALL dsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
654  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
655  infot = 5
656  CALL dsysv_rook( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
657  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
658  infot = 8
659  CALL dsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
660  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
661  infot = 10
662  CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
663  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
664  infot = 10
665  CALL dsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
666  CALL chkxer( 'DSYSV_ROOK', infot, nout, lerr, ok )
667 *
668  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
669 *
670 * DSYSV_RK
671 *
672 * Test error exits of the driver that uses factorization
673 * of a symmetric indefinite matrix with rook
674 * (bounded Bunch-Kaufman) pivoting with the new storage
675 * format for factors L ( or U) and D.
676 *
677 * L (or U) is stored in A, diagonal of D is stored on the
678 * diagonal of A, subdiagonal of D is stored in a separate array E.
679 *
680  srnamt = 'DSYSV_RK'
681  infot = 1
682  CALL dsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
683  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
684  infot = 2
685  CALL dsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
686  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
687  infot = 3
688  CALL dsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
689  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
690  infot = 5
691  CALL dsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
692  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
693  infot = 9
694  CALL dsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
695  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
696  infot = 11
697  CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
698  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
699  infot = 11
700  CALL dsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
701  CALL chkxer( 'DSYSV_RK', infot, nout, lerr, ok )
702 *
703  ELSE IF( lsamen( 2, c2, 'SA' ) ) THEN
704 *
705 * DSYSV_AA
706 *
707  srnamt = 'DSYSV_AA'
708  infot = 1
709  CALL dsysv_aa( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
710  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
711  infot = 2
712  CALL dsysv_aa( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
713  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
714  infot = 3
715  CALL dsysv_aa( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
716  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
717  infot = 8
718  CALL dsysv_aa( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
719  CALL chkxer( 'DSYSV_AA', infot, nout, lerr, ok )
720 *
721  ELSE IF( lsamen( 2, c2, 'S2' ) ) THEN
722 *
723 * DSYSV_AASEN_2STAGE
724 *
725  srnamt = 'DSYSV_AA_2STAGE'
726  infot = 1
727  CALL dsysv_aa_2stage( '/', 0, 0, a, 1, a, 1, ip, ip, b, 1,
728  $ w, 1, info )
729  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
730  infot = 2
731  CALL dsysv_aa_2stage( 'U', -1, 0, a, 1, a, 1, ip, ip, b, 1,
732  $ w, 1, info )
733  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
734  infot = 3
735  CALL dsysv_aa_2stage( 'U', 0, -1, a, 1, a, 1, ip, ip, b, 1,
736  $ w, 1, info )
737  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
738  infot = 5
739  CALL dsysv_aa_2stage( 'U', 2, 1, a, 1, a, 1, ip, ip, b, 1,
740  $ w, 1, info )
741  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
742  infot = 11
743  CALL dsysv_aa_2stage( 'U', 2, 1, a, 2, a, 8, ip, ip, b, 1,
744  $ w, 1, info )
745  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
746  infot = 7
747  CALL dsysv_aa_2stage( 'U', 2, 1, a, 2, a, 1, ip, ip, b, 2,
748  $ w, 1, info )
749  CALL chkxer( 'DSYSV_AA_2STAGE', infot, nout, lerr, ok )
750 *
751  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
752 *
753 * DSPSV
754 *
755  srnamt = 'DSPSV '
756  infot = 1
757  CALL dspsv( '/', 0, 0, a, ip, b, 1, info )
758  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
759  infot = 2
760  CALL dspsv( 'U', -1, 0, a, ip, b, 1, info )
761  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
762  infot = 3
763  CALL dspsv( 'U', 0, -1, a, ip, b, 1, info )
764  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
765  infot = 7
766  CALL dspsv( 'U', 2, 0, a, ip, b, 1, info )
767  CALL chkxer( 'DSPSV ', infot, nout, lerr, ok )
768 *
769 * DSPSVX
770 *
771  srnamt = 'DSPSVX'
772  infot = 1
773  CALL dspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
774  $ r2, w, iw, info )
775  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
776  infot = 2
777  CALL dspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
778  $ r2, w, iw, info )
779  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
780  infot = 3
781  CALL dspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
782  $ r2, w, iw, info )
783  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
784  infot = 4
785  CALL dspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
786  $ r2, w, iw, info )
787  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
788  infot = 9
789  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
790  $ r2, w, iw, info )
791  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
792  infot = 11
793  CALL dspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
794  $ r2, w, iw, info )
795  CALL chkxer( 'DSPSVX', infot, nout, lerr, ok )
796  END IF
797 *
798 * Print a summary line.
799 *
800  IF( ok ) THEN
801  WRITE( nout, fmt = 9999 )path
802  ELSE
803  WRITE( nout, fmt = 9998 )path
804  END IF
805 *
806  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
807  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
808  $ 'exits ***' )
809 *
810  RETURN
811 *
812 * End of DERRVX
813 *
814  END
dgtsv
subroutine dgtsv(N, NRHS, DL, D, DU, B, LDB, INFO)
DGTSV computes the solution to system of linear equations A * X = B for GT matrices
Definition: dgtsv.f:129
dsysv_aa
subroutine dsysv_aa(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
DSYSV_AA computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysv_aa.f:164
derrvx
subroutine derrvx(PATH, NUNIT)
DERRVX
Definition: derrvx.f:57
dposvx
subroutine dposvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DPOSVX computes the solution to system of linear equations A * X = B for PO matrices
Definition: dposvx.f:309
dpbsvx
subroutine dpbsvx(FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dpbsvx.f:345
dgesvx
subroutine dgesvx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DGESVX computes the solution to system of linear equations A * X = B for GE matrices
Definition: dgesvx.f:351
dppsvx
subroutine dppsvx(FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dppsvx.f:313
dsysv
subroutine dsysv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
DSYSV computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysv.f:173
dgtsvx
subroutine dgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DGTSVX computes the solution to system of linear equations A * X = B for GT matrices
Definition: dgtsvx.f:295
dptsvx
subroutine dptsvx(FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, INFO)
DPTSVX computes the solution to system of linear equations A * X = B for PT matrices
Definition: dptsvx.f:230
chkxer
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
dspsv
subroutine dspsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
DSPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dspsv.f:164
dposv
subroutine dposv(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
DPOSV computes the solution to system of linear equations A * X = B for PO matrices
Definition: dposv.f:132
dgesv
subroutine dgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
DGESV computes the solution to system of linear equations A * X = B for GE matrices
Definition: dgesv.f:124
dgbsvx
subroutine dgbsvx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DGBSVX computes the solution to system of linear equations A * X = B for GB matrices
Definition: dgbsvx.f:371
dsysv_rk
subroutine dsysv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
DSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysv_rk.f:230
dsysv_rook
subroutine dsysv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
DSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysv_rook.f:206
dsysv_aa_2stage
subroutine dsysv_aa_2stage(UPLO, N, NRHS, A, LDA, TB, LTB, IPIV, IPIV2, B, LDB, WORK, LWORK, INFO)
DSYSV_AA_2STAGE computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysv_aa_2stage.f:190
dspsvx
subroutine dspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, IWORK, INFO)
DSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dspsvx.f:278
dgbsv
subroutine dgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
DGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver)
Definition: dgbsv.f:164
dpbsv
subroutine dpbsv(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
DPBSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dpbsv.f:166
dppsv
subroutine dppsv(UPLO, N, NRHS, AP, B, LDB, INFO)
DPPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition: dppsv.f:146
dsysvx
subroutine dsysvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, IWORK, INFO)
DSYSVX computes the solution to system of linear equations A * X = B for SY matrices
Definition: dsysvx.f:286
dptsv
subroutine dptsv(N, NRHS, D, E, B, LDB, INFO)
DPTSV computes the solution to system of linear equations A * X = B for PT matrices
Definition: dptsv.f:116