LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
derrbd.f
Go to the documentation of this file.
1 *> \brief \b DERRBD
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 DERRBD( 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 *> DERRBD tests the error exits for DGEBRD, DORGBR, DORMBR, DBDSQR and
25 *> DBDSDC.
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 2011
52 *
53 *> \ingroup double_eig
54 *
55 * =====================================================================
56  SUBROUTINE derrbd( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.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 2011
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 path
65  INTEGER nunit
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER nmax, lw
72  parameter( nmax = 4, lw = nmax )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER*2 c2
76  INTEGER i, info, j, nt
77 * ..
78 * .. Local Arrays ..
79  INTEGER iq( nmax, nmax ), iw( nmax )
80  DOUBLE PRECISION a( nmax, nmax ), d( nmax ), e( nmax ),
81  $ q( nmax, nmax ), tp( nmax ), tq( nmax ),
82  $ u( nmax, nmax ), v( nmax, nmax ), w( lw )
83 * ..
84 * .. External Functions ..
85  LOGICAL lsamen
86  EXTERNAL lsamen
87 * ..
88 * .. External Subroutines ..
89  EXTERNAL chkxer, dbdsdc, dbdsqr, dgebd2, dgebrd, dorgbr,
90  $ dormbr
91 * ..
92 * .. Scalars in Common ..
93  LOGICAL lerr, ok
94  CHARACTER*32 srnamt
95  INTEGER infot, nout
96 * ..
97 * .. Common blocks ..
98  common / infoc / infot, nout, ok, lerr
99  common / srnamc / srnamt
100 * ..
101 * .. Intrinsic Functions ..
102  INTRINSIC dble
103 * ..
104 * .. Executable Statements ..
105 *
106  nout = nunit
107  WRITE( nout, fmt = * )
108  c2 = path( 2: 3 )
109 *
110 * Set the variables to innocuous values.
111 *
112  DO 20 j = 1, nmax
113  DO 10 i = 1, nmax
114  a( i, j ) = 1.d0 / dble( i+j )
115  10 continue
116  20 continue
117  ok = .true.
118  nt = 0
119 *
120 * Test error exits of the SVD routines.
121 *
122  IF( lsamen( 2, c2, 'BD' ) ) THEN
123 *
124 * DGEBRD
125 *
126  srnamt = 'DGEBRD'
127  infot = 1
128  CALL dgebrd( -1, 0, a, 1, d, e, tq, tp, w, 1, info )
129  CALL chkxer( 'DGEBRD', infot, nout, lerr, ok )
130  infot = 2
131  CALL dgebrd( 0, -1, a, 1, d, e, tq, tp, w, 1, info )
132  CALL chkxer( 'DGEBRD', infot, nout, lerr, ok )
133  infot = 4
134  CALL dgebrd( 2, 1, a, 1, d, e, tq, tp, w, 2, info )
135  CALL chkxer( 'DGEBRD', infot, nout, lerr, ok )
136  infot = 10
137  CALL dgebrd( 2, 1, a, 2, d, e, tq, tp, w, 1, info )
138  CALL chkxer( 'DGEBRD', infot, nout, lerr, ok )
139  nt = nt + 4
140 *
141 * DGEBD2
142 *
143  srnamt = 'DGEBD2'
144  infot = 1
145  CALL dgebd2( -1, 0, a, 1, d, e, tq, tp, w, info )
146  CALL chkxer( 'DGEBD2', infot, nout, lerr, ok )
147  infot = 2
148  CALL dgebd2( 0, -1, a, 1, d, e, tq, tp, w, info )
149  CALL chkxer( 'DGEBD2', infot, nout, lerr, ok )
150  infot = 4
151  CALL dgebd2( 2, 1, a, 1, d, e, tq, tp, w, info )
152  CALL chkxer( 'DGEBD2', infot, nout, lerr, ok )
153  nt = nt + 3
154 *
155 * DORGBR
156 *
157  srnamt = 'DORGBR'
158  infot = 1
159  CALL dorgbr( '/', 0, 0, 0, a, 1, tq, w, 1, info )
160  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
161  infot = 2
162  CALL dorgbr( 'Q', -1, 0, 0, a, 1, tq, w, 1, info )
163  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
164  infot = 3
165  CALL dorgbr( 'Q', 0, -1, 0, a, 1, tq, w, 1, info )
166  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
167  infot = 3
168  CALL dorgbr( 'Q', 0, 1, 0, a, 1, tq, w, 1, info )
169  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
170  infot = 3
171  CALL dorgbr( 'Q', 1, 0, 1, a, 1, tq, w, 1, info )
172  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
173  infot = 3
174  CALL dorgbr( 'P', 1, 0, 0, a, 1, tq, w, 1, info )
175  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
176  infot = 3
177  CALL dorgbr( 'P', 0, 1, 1, a, 1, tq, w, 1, info )
178  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
179  infot = 4
180  CALL dorgbr( 'Q', 0, 0, -1, a, 1, tq, w, 1, info )
181  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
182  infot = 6
183  CALL dorgbr( 'Q', 2, 1, 1, a, 1, tq, w, 1, info )
184  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
185  infot = 9
186  CALL dorgbr( 'Q', 2, 2, 1, a, 2, tq, w, 1, info )
187  CALL chkxer( 'DORGBR', infot, nout, lerr, ok )
188  nt = nt + 10
189 *
190 * DORMBR
191 *
192  srnamt = 'DORMBR'
193  infot = 1
194  CALL dormbr( '/', 'L', 'T', 0, 0, 0, a, 1, tq, u, 1, w, 1,
195  $ info )
196  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
197  infot = 2
198  CALL dormbr( 'Q', '/', 'T', 0, 0, 0, a, 1, tq, u, 1, w, 1,
199  $ info )
200  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
201  infot = 3
202  CALL dormbr( 'Q', 'L', '/', 0, 0, 0, a, 1, tq, u, 1, w, 1,
203  $ info )
204  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
205  infot = 4
206  CALL dormbr( 'Q', 'L', 'T', -1, 0, 0, a, 1, tq, u, 1, w, 1,
207  $ info )
208  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
209  infot = 5
210  CALL dormbr( 'Q', 'L', 'T', 0, -1, 0, a, 1, tq, u, 1, w, 1,
211  $ info )
212  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
213  infot = 6
214  CALL dormbr( 'Q', 'L', 'T', 0, 0, -1, a, 1, tq, u, 1, w, 1,
215  $ info )
216  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
217  infot = 8
218  CALL dormbr( 'Q', 'L', 'T', 2, 0, 0, a, 1, tq, u, 2, w, 1,
219  $ info )
220  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
221  infot = 8
222  CALL dormbr( 'Q', 'R', 'T', 0, 2, 0, a, 1, tq, u, 1, w, 1,
223  $ info )
224  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
225  infot = 8
226  CALL dormbr( 'P', 'L', 'T', 2, 0, 2, a, 1, tq, u, 2, w, 1,
227  $ info )
228  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
229  infot = 8
230  CALL dormbr( 'P', 'R', 'T', 0, 2, 2, a, 1, tq, u, 1, w, 1,
231  $ info )
232  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
233  infot = 11
234  CALL dormbr( 'Q', 'R', 'T', 2, 0, 0, a, 1, tq, u, 1, w, 1,
235  $ info )
236  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
237  infot = 13
238  CALL dormbr( 'Q', 'L', 'T', 0, 2, 0, a, 1, tq, u, 1, w, 1,
239  $ info )
240  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
241  infot = 13
242  CALL dormbr( 'Q', 'R', 'T', 2, 0, 0, a, 1, tq, u, 2, w, 1,
243  $ info )
244  CALL chkxer( 'DORMBR', infot, nout, lerr, ok )
245  nt = nt + 13
246 *
247 * DBDSQR
248 *
249  srnamt = 'DBDSQR'
250  infot = 1
251  CALL dbdsqr( '/', 0, 0, 0, 0, d, e, v, 1, u, 1, a, 1, w, info )
252  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
253  infot = 2
254  CALL dbdsqr( 'U', -1, 0, 0, 0, d, e, v, 1, u, 1, a, 1, w,
255  $ info )
256  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
257  infot = 3
258  CALL dbdsqr( 'U', 0, -1, 0, 0, d, e, v, 1, u, 1, a, 1, w,
259  $ info )
260  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
261  infot = 4
262  CALL dbdsqr( 'U', 0, 0, -1, 0, d, e, v, 1, u, 1, a, 1, w,
263  $ info )
264  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
265  infot = 5
266  CALL dbdsqr( 'U', 0, 0, 0, -1, d, e, v, 1, u, 1, a, 1, w,
267  $ info )
268  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
269  infot = 9
270  CALL dbdsqr( 'U', 2, 1, 0, 0, d, e, v, 1, u, 1, a, 1, w, info )
271  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
272  infot = 11
273  CALL dbdsqr( 'U', 0, 0, 2, 0, d, e, v, 1, u, 1, a, 1, w, info )
274  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
275  infot = 13
276  CALL dbdsqr( 'U', 2, 0, 0, 1, d, e, v, 1, u, 1, a, 1, w, info )
277  CALL chkxer( 'DBDSQR', infot, nout, lerr, ok )
278  nt = nt + 8
279 *
280 * DBDSDC
281 *
282  srnamt = 'DBDSDC'
283  infot = 1
284  CALL dbdsdc( '/', 'N', 0, d, e, u, 1, v, 1, q, iq, w, iw,
285  $ info )
286  CALL chkxer( 'DBDSDC', infot, nout, lerr, ok )
287  infot = 2
288  CALL dbdsdc( 'U', '/', 0, d, e, u, 1, v, 1, q, iq, w, iw,
289  $ info )
290  CALL chkxer( 'DBDSDC', infot, nout, lerr, ok )
291  infot = 3
292  CALL dbdsdc( 'U', 'N', -1, d, e, u, 1, v, 1, q, iq, w, iw,
293  $ info )
294  CALL chkxer( 'DBDSDC', infot, nout, lerr, ok )
295  infot = 7
296  CALL dbdsdc( 'U', 'I', 2, d, e, u, 1, v, 1, q, iq, w, iw,
297  $ info )
298  CALL chkxer( 'DBDSDC', infot, nout, lerr, ok )
299  infot = 9
300  CALL dbdsdc( 'U', 'I', 2, d, e, u, 2, v, 1, q, iq, w, iw,
301  $ info )
302  CALL chkxer( 'DBDSDC', infot, nout, lerr, ok )
303  nt = nt + 5
304  END IF
305 *
306 * Print a summary line.
307 *
308  IF( ok ) THEN
309  WRITE( nout, fmt = 9999 )path, nt
310  ELSE
311  WRITE( nout, fmt = 9998 )path
312  END IF
313 *
314  9999 format( 1x, a3, ' routines passed the tests of the error exits',
315  $ ' (', i3, ' tests done)' )
316  9998 format( ' *** ', a3, ' routines failed the tests of the error ',
317  $ 'exits ***' )
318 *
319  return
320 *
321 * End of DERRBD
322 *
323  END