LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
derrls.f
Go to the documentation of this file.
1 *> \brief \b DERRLS
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 DERRLS( 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 *> DERRLS tests the error exits for the DOUBLE PRECISION least squares
25 *> driver routines (DGELS, SGELSS, SGELSY, SGELSD).
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 2015
52 *
53 *> \ingroup double_lin
54 *
55 * =====================================================================
56  SUBROUTINE derrls( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.6.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 2015
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 PATH
65  INTEGER NUNIT
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER NMAX
72  parameter ( nmax = 2 )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER*2 C2
76  INTEGER INFO, IRNK
77  DOUBLE PRECISION RCOND
78 * ..
79 * .. Local Arrays ..
80  INTEGER IP( nmax )
81  DOUBLE PRECISION A( nmax, nmax ), B( nmax, nmax ), S( nmax ),
82  $ w( nmax )
83 * ..
84 * .. External Functions ..
85  LOGICAL LSAMEN
86  EXTERNAL lsamen
87 * ..
88 * .. External Subroutines ..
89  EXTERNAL alaesm, chkxer, dgels, dgelsd, dgelss, dgelsy
90 * ..
91 * .. Scalars in Common ..
92  LOGICAL LERR, OK
93  CHARACTER*32 SRNAMT
94  INTEGER INFOT, NOUT
95 * ..
96 * .. Common blocks ..
97  COMMON / infoc / infot, nout, ok, lerr
98  COMMON / srnamc / srnamt
99 * ..
100 * .. Executable Statements ..
101 *
102  nout = nunit
103  WRITE( nout, fmt = * )
104  c2 = path( 2: 3 )
105  a( 1, 1 ) = 1.0d+0
106  a( 1, 2 ) = 2.0d+0
107  a( 2, 2 ) = 3.0d+0
108  a( 2, 1 ) = 4.0d+0
109  ok = .true.
110 *
111  IF( lsamen( 2, c2, 'LS' ) ) THEN
112 *
113 * Test error exits for the least squares driver routines.
114 *
115 * DGELS
116 *
117  srnamt = 'DGELS '
118  infot = 1
119  CALL dgels( '/', 0, 0, 0, a, 1, b, 1, w, 1, info )
120  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
121  infot = 2
122  CALL dgels( 'N', -1, 0, 0, a, 1, b, 1, w, 1, info )
123  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
124  infot = 3
125  CALL dgels( 'N', 0, -1, 0, a, 1, b, 1, w, 1, info )
126  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
127  infot = 4
128  CALL dgels( 'N', 0, 0, -1, a, 1, b, 1, w, 1, info )
129  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
130  infot = 6
131  CALL dgels( 'N', 2, 0, 0, a, 1, b, 2, w, 2, info )
132  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
133  infot = 8
134  CALL dgels( 'N', 2, 0, 0, a, 2, b, 1, w, 2, info )
135  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
136  infot = 10
137  CALL dgels( 'N', 1, 1, 0, a, 1, b, 1, w, 1, info )
138  CALL chkxer( 'DGELS ', infot, nout, lerr, ok )
139 *
140 * DGELSS
141 *
142  srnamt = 'DGELSS'
143  infot = 1
144  CALL dgelss( -1, 0, 0, a, 1, b, 1, s, rcond, irnk, w, 1, info )
145  CALL chkxer( 'DGELSS', infot, nout, lerr, ok )
146  infot = 2
147  CALL dgelss( 0, -1, 0, a, 1, b, 1, s, rcond, irnk, w, 1, info )
148  CALL chkxer( 'DGELSS', infot, nout, lerr, ok )
149  infot = 3
150  CALL dgelss( 0, 0, -1, a, 1, b, 1, s, rcond, irnk, w, 1, info )
151  CALL chkxer( 'DGELSS', infot, nout, lerr, ok )
152  infot = 5
153  CALL dgelss( 2, 0, 0, a, 1, b, 2, s, rcond, irnk, w, 2, info )
154  CALL chkxer( 'DGELSS', infot, nout, lerr, ok )
155  infot = 7
156  CALL dgelss( 2, 0, 0, a, 2, b, 1, s, rcond, irnk, w, 2, info )
157  CALL chkxer( 'DGELSS', infot, nout, lerr, ok )
158 *
159 * DGELSY
160 *
161  srnamt = 'DGELSY'
162  infot = 1
163  CALL dgelsy( -1, 0, 0, a, 1, b, 1, ip, rcond, irnk, w, 10,
164  $ info )
165  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
166  infot = 2
167  CALL dgelsy( 0, -1, 0, a, 1, b, 1, ip, rcond, irnk, w, 10,
168  $ info )
169  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
170  infot = 3
171  CALL dgelsy( 0, 0, -1, a, 1, b, 1, ip, rcond, irnk, w, 10,
172  $ info )
173  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
174  infot = 5
175  CALL dgelsy( 2, 0, 0, a, 1, b, 2, ip, rcond, irnk, w, 10,
176  $ info )
177  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
178  infot = 7
179  CALL dgelsy( 2, 0, 0, a, 2, b, 1, ip, rcond, irnk, w, 10,
180  $ info )
181  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
182  infot = 12
183  CALL dgelsy( 2, 2, 1, a, 2, b, 2, ip, rcond, irnk, w, 1, info )
184  CALL chkxer( 'DGELSY', infot, nout, lerr, ok )
185 *
186 * DGELSD
187 *
188  srnamt = 'DGELSD'
189  infot = 1
190  CALL dgelsd( -1, 0, 0, a, 1, b, 1, s, rcond, irnk, w, 10, ip,
191  $ info )
192  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
193  infot = 2
194  CALL dgelsd( 0, -1, 0, a, 1, b, 1, s, rcond, irnk, w, 10, ip,
195  $ info )
196  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
197  infot = 3
198  CALL dgelsd( 0, 0, -1, a, 1, b, 1, s, rcond, irnk, w, 10, ip,
199  $ info )
200  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
201  infot = 5
202  CALL dgelsd( 2, 0, 0, a, 1, b, 2, s, rcond, irnk, w, 10, ip,
203  $ info )
204  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
205  infot = 7
206  CALL dgelsd( 2, 0, 0, a, 2, b, 1, s, rcond, irnk, w, 10, ip,
207  $ info )
208  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
209  infot = 12
210  CALL dgelsd( 2, 2, 1, a, 2, b, 2, s, rcond, irnk, w, 1, ip,
211  $ info )
212  CALL chkxer( 'DGELSD', infot, nout, lerr, ok )
213  END IF
214 *
215 * Print a summary line.
216 *
217  CALL alaesm( path, ok, nout )
218 *
219  RETURN
220 *
221 * End of DERRLS
222 *
223  END
subroutine derrls(PATH, NUNIT)
DERRLS
Definition: derrls.f:57
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine dgelsd(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, IWORK, INFO)
DGELSD computes the minimum-norm solution to a linear least squares problem for GE matrices ...
Definition: dgelsd.f:211
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine dgelss(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, INFO)
DGELSS solves overdetermined or underdetermined systems for GE matrices
Definition: dgelss.f:174
subroutine dgels(TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK, INFO)
DGELS solves overdetermined or underdetermined systems for GE matrices
Definition: dgels.f:185
subroutine dgelsy(M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK, WORK, LWORK, INFO)
DGELSY solves overdetermined or underdetermined systems for GE matrices
Definition: dgelsy.f:206