LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cerrls.f
Go to the documentation of this file.
1 *> \brief \b CERRLS
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 CERRLS( 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 *> CERRLS tests the error exits for the COMPLEX least squares
25 *> driver routines (CGELS, CGELSS, CGELSY, CGELSD).
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 complex_lin
54 *
55 * =====================================================================
56  SUBROUTINE cerrls( 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  REAL RCOND
78 * ..
79 * .. Local Arrays ..
80  INTEGER IP( nmax )
81  REAL RW( nmax ), S( nmax )
82  COMPLEX A( nmax, nmax ), B( nmax, nmax ), W( nmax )
83 * ..
84 * .. External Functions ..
85  LOGICAL LSAMEN
86  EXTERNAL lsamen
87 * ..
88 * .. External Subroutines ..
89  EXTERNAL alaesm, cgels, cgelsd, cgelss, cgelsy, chkxer
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  c2 = path( 2: 3 )
104  a( 1, 1 ) = ( 1.0e+0, 0.0e+0 )
105  a( 1, 2 ) = ( 2.0e+0, 0.0e+0 )
106  a( 2, 2 ) = ( 3.0e+0, 0.0e+0 )
107  a( 2, 1 ) = ( 4.0e+0, 0.0e+0 )
108  ok = .true.
109  WRITE( nout, fmt = * )
110 *
111 * Test error exits for the least squares driver routines.
112 *
113  IF( lsamen( 2, c2, 'LS' ) ) THEN
114 *
115 * CGELS
116 *
117  srnamt = 'CGELS '
118  infot = 1
119  CALL cgels( '/', 0, 0, 0, a, 1, b, 1, w, 1, info )
120  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
121  infot = 2
122  CALL cgels( 'N', -1, 0, 0, a, 1, b, 1, w, 1, info )
123  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
124  infot = 3
125  CALL cgels( 'N', 0, -1, 0, a, 1, b, 1, w, 1, info )
126  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
127  infot = 4
128  CALL cgels( 'N', 0, 0, -1, a, 1, b, 1, w, 1, info )
129  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
130  infot = 6
131  CALL cgels( 'N', 2, 0, 0, a, 1, b, 2, w, 2, info )
132  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
133  infot = 8
134  CALL cgels( 'N', 2, 0, 0, a, 2, b, 1, w, 2, info )
135  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
136  infot = 10
137  CALL cgels( 'N', 1, 1, 0, a, 1, b, 1, w, 1, info )
138  CALL chkxer( 'CGELS ', infot, nout, lerr, ok )
139 *
140 * CGELSS
141 *
142  srnamt = 'CGELSS'
143  infot = 1
144  CALL cgelss( -1, 0, 0, a, 1, b, 1, s, rcond, irnk, w, 1, rw,
145  $ info )
146  CALL chkxer( 'CGELSS', infot, nout, lerr, ok )
147  infot = 2
148  CALL cgelss( 0, -1, 0, a, 1, b, 1, s, rcond, irnk, w, 1, rw,
149  $ info )
150  CALL chkxer( 'CGELSS', infot, nout, lerr, ok )
151  infot = 3
152  CALL cgelss( 0, 0, -1, a, 1, b, 1, s, rcond, irnk, w, 1, rw,
153  $ info )
154  CALL chkxer( 'CGELSS', infot, nout, lerr, ok )
155  infot = 5
156  CALL cgelss( 2, 0, 0, a, 1, b, 2, s, rcond, irnk, w, 2, rw,
157  $ info )
158  CALL chkxer( 'CGELSS', infot, nout, lerr, ok )
159  infot = 7
160  CALL cgelss( 2, 0, 0, a, 2, b, 1, s, rcond, irnk, w, 2, rw,
161  $ info )
162  CALL chkxer( 'CGELSS', infot, nout, lerr, ok )
163 *
164 * CGELSY
165 *
166  srnamt = 'CGELSY'
167  infot = 1
168  CALL cgelsy( -1, 0, 0, a, 1, b, 1, ip, rcond, irnk, w, 10, rw,
169  $ info )
170  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
171  infot = 2
172  CALL cgelsy( 0, -1, 0, a, 1, b, 1, ip, rcond, irnk, w, 10, rw,
173  $ info )
174  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
175  infot = 3
176  CALL cgelsy( 0, 0, -1, a, 1, b, 1, ip, rcond, irnk, w, 10, rw,
177  $ info )
178  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
179  infot = 5
180  CALL cgelsy( 2, 0, 0, a, 1, b, 2, ip, rcond, irnk, w, 10, rw,
181  $ info )
182  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
183  infot = 7
184  CALL cgelsy( 2, 0, 0, a, 2, b, 1, ip, rcond, irnk, w, 10, rw,
185  $ info )
186  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
187  infot = 12
188  CALL cgelsy( 0, 3, 0, a, 1, b, 3, ip, rcond, irnk, w, 1, rw,
189  $ info )
190  CALL chkxer( 'CGELSY', infot, nout, lerr, ok )
191 *
192 * CGELSD
193 *
194  srnamt = 'CGELSD'
195  infot = 1
196  CALL cgelsd( -1, 0, 0, a, 1, b, 1, s, rcond, irnk, w, 10,
197  $ rw, ip, info )
198  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
199  infot = 2
200  CALL cgelsd( 0, -1, 0, a, 1, b, 1, s, rcond, irnk, w, 10,
201  $ rw, ip, info )
202  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
203  infot = 3
204  CALL cgelsd( 0, 0, -1, a, 1, b, 1, s, rcond, irnk, w, 10,
205  $ rw, ip, info )
206  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
207  infot = 5
208  CALL cgelsd( 2, 0, 0, a, 1, b, 2, s, rcond, irnk, w, 10,
209  $ rw, ip, info )
210  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
211  infot = 7
212  CALL cgelsd( 2, 0, 0, a, 2, b, 1, s, rcond, irnk, w, 10,
213  $ rw, ip, info )
214  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
215  infot = 12
216  CALL cgelsd( 2, 2, 1, a, 2, b, 2, s, rcond, irnk, w, 1,
217  $ rw, ip, info )
218  CALL chkxer( 'CGELSD', infot, nout, lerr, ok )
219  END IF
220 *
221 * Print a summary line.
222 *
223  CALL alaesm( path, ok, nout )
224 *
225  RETURN
226 *
227 * End of CERRLS
228 *
229  END
subroutine alaesm(PATH, OK, NOUT)
ALAESM
Definition: alaesm.f:65
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine cgelsd(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, RWORK, IWORK, INFO)
CGELSD computes the minimum-norm solution to a linear least squares problem for GE matrices ...
Definition: cgelsd.f:227
subroutine cgelss(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, RWORK, INFO)
CGELSS solves overdetermined or underdetermined systems for GE matrices
Definition: cgelss.f:180
subroutine cgels(TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK, INFO)
CGELS solves overdetermined or underdetermined systems for GE matrices
Definition: cgels.f:184
subroutine cgelsy(M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK, WORK, LWORK, RWORK, INFO)
CGELSY solves overdetermined or underdetermined systems for GE matrices
Definition: cgelsy.f:212
subroutine cerrls(PATH, NUNIT)
CERRLS
Definition: cerrls.f:57