LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cerrlq.f
Go to the documentation of this file.
1*> \brief \b CERRLQ
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 CERRLQ( 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*> CERRLQ tests the error exits for the COMPLEX routines
25*> that use the LQ decomposition of a general matrix.
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*> \ingroup complex_lin
52*
53* =====================================================================
54 SUBROUTINE cerrlq( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 2 )
70* ..
71* .. Local Scalars ..
72 INTEGER I, INFO, J
73* ..
74* .. Local Arrays ..
75 COMPLEX A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
76 $ W( NMAX ), X( NMAX )
77* ..
78* .. External Subroutines ..
79 EXTERNAL alaesm, cgelq2, cgelqf, chkxer, cungl2,
81* ..
82* .. Scalars in Common ..
83 LOGICAL LERR, OK
84 CHARACTER*32 SRNAMT
85 INTEGER INFOT, NOUT
86* ..
87* .. Common blocks ..
88 COMMON / infoc / infot, nout, ok, lerr
89 COMMON / srnamc / srnamt
90* ..
91* .. Intrinsic Functions ..
92 INTRINSIC cmplx, real
93* ..
94* .. Executable Statements ..
95*
96 nout = nunit
97 WRITE( nout, fmt = * )
98*
99* Set the variables to innocuous values.
100*
101 DO 20 j = 1, nmax
102 DO 10 i = 1, nmax
103 a( i, j ) = cmplx( 1. / real( i+j ), -1. / real( i+j ) )
104 af( i, j ) = cmplx( 1. / real( i+j ), -1. / real( i+j ) )
105 10 CONTINUE
106 b( j ) = 0.
107 w( j ) = 0.
108 x( j ) = 0.
109 20 CONTINUE
110 ok = .true.
111*
112* Error exits for LQ factorization
113*
114* CGELQF
115*
116 srnamt = 'CGELQF'
117 infot = 1
118 CALL cgelqf( -1, 0, a, 1, b, w, 1, info )
119 CALL chkxer( 'CGELQF', infot, nout, lerr, ok )
120 infot = 2
121 CALL cgelqf( 0, -1, a, 1, b, w, 1, info )
122 CALL chkxer( 'CGELQF', infot, nout, lerr, ok )
123 infot = 4
124 CALL cgelqf( 2, 1, a, 1, b, w, 2, info )
125 CALL chkxer( 'CGELQF', infot, nout, lerr, ok )
126 infot = 7
127 CALL cgelqf( 2, 1, a, 2, b, w, 1, info )
128 CALL chkxer( 'CGELQF', infot, nout, lerr, ok )
129*
130* CGELQ2
131*
132 srnamt = 'CGELQ2'
133 infot = 1
134 CALL cgelq2( -1, 0, a, 1, b, w, info )
135 CALL chkxer( 'CGELQ2', infot, nout, lerr, ok )
136 infot = 2
137 CALL cgelq2( 0, -1, a, 1, b, w, info )
138 CALL chkxer( 'CGELQ2', infot, nout, lerr, ok )
139 infot = 4
140 CALL cgelq2( 2, 1, a, 1, b, w, info )
141 CALL chkxer( 'CGELQ2', infot, nout, lerr, ok )
142*
143* CUNGLQ
144*
145 srnamt = 'CUNGLQ'
146 infot = 1
147 CALL cunglq( -1, 0, 0, a, 1, x, w, 1, info )
148 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
149 infot = 2
150 CALL cunglq( 0, -1, 0, a, 1, x, w, 1, info )
151 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
152 infot = 2
153 CALL cunglq( 2, 1, 0, a, 2, x, w, 2, info )
154 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
155 infot = 3
156 CALL cunglq( 0, 0, -1, a, 1, x, w, 1, info )
157 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
158 infot = 3
159 CALL cunglq( 1, 1, 2, a, 1, x, w, 1, info )
160 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
161 infot = 5
162 CALL cunglq( 2, 2, 0, a, 1, x, w, 2, info )
163 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
164 infot = 8
165 CALL cunglq( 2, 2, 0, a, 2, x, w, 1, info )
166 CALL chkxer( 'CUNGLQ', infot, nout, lerr, ok )
167*
168* CUNGL2
169*
170 srnamt = 'CUNGL2'
171 infot = 1
172 CALL cungl2( -1, 0, 0, a, 1, x, w, info )
173 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
174 infot = 2
175 CALL cungl2( 0, -1, 0, a, 1, x, w, info )
176 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
177 infot = 2
178 CALL cungl2( 2, 1, 0, a, 2, x, w, info )
179 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
180 infot = 3
181 CALL cungl2( 0, 0, -1, a, 1, x, w, info )
182 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
183 infot = 3
184 CALL cungl2( 1, 1, 2, a, 1, x, w, info )
185 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
186 infot = 5
187 CALL cungl2( 2, 2, 0, a, 1, x, w, info )
188 CALL chkxer( 'CUNGL2', infot, nout, lerr, ok )
189*
190* CUNMLQ
191*
192 srnamt = 'CUNMLQ'
193 infot = 1
194 CALL cunmlq( '/', 'N', 0, 0, 0, a, 1, x, af, 1, w, 1, info )
195 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
196 infot = 2
197 CALL cunmlq( 'L', '/', 0, 0, 0, a, 1, x, af, 1, w, 1, info )
198 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
199 infot = 3
200 CALL cunmlq( 'L', 'N', -1, 0, 0, a, 1, x, af, 1, w, 1, info )
201 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
202 infot = 4
203 CALL cunmlq( 'L', 'N', 0, -1, 0, a, 1, x, af, 1, w, 1, info )
204 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
205 infot = 5
206 CALL cunmlq( 'L', 'N', 0, 0, -1, a, 1, x, af, 1, w, 1, info )
207 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
208 infot = 5
209 CALL cunmlq( 'L', 'N', 0, 1, 1, a, 1, x, af, 1, w, 1, info )
210 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
211 infot = 5
212 CALL cunmlq( 'R', 'N', 1, 0, 1, a, 1, x, af, 1, w, 1, info )
213 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
214 infot = 7
215 CALL cunmlq( 'L', 'N', 2, 0, 2, a, 1, x, af, 2, w, 1, info )
216 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
217 infot = 7
218 CALL cunmlq( 'R', 'N', 0, 2, 2, a, 1, x, af, 1, w, 1, info )
219 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
220 infot = 10
221 CALL cunmlq( 'L', 'N', 2, 1, 0, a, 2, x, af, 1, w, 1, info )
222 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
223 infot = 12
224 CALL cunmlq( 'L', 'N', 1, 2, 0, a, 1, x, af, 1, w, 1, info )
225 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
226 infot = 12
227 CALL cunmlq( 'R', 'N', 2, 1, 0, a, 1, x, af, 2, w, 1, info )
228 CALL chkxer( 'CUNMLQ', infot, nout, lerr, ok )
229*
230* CUNML2
231*
232 srnamt = 'CUNML2'
233 infot = 1
234 CALL cunml2( '/', 'N', 0, 0, 0, a, 1, x, af, 1, w, info )
235 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
236 infot = 2
237 CALL cunml2( 'L', '/', 0, 0, 0, a, 1, x, af, 1, w, info )
238 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
239 infot = 3
240 CALL cunml2( 'L', 'N', -1, 0, 0, a, 1, x, af, 1, w, info )
241 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
242 infot = 4
243 CALL cunml2( 'L', 'N', 0, -1, 0, a, 1, x, af, 1, w, info )
244 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
245 infot = 5
246 CALL cunml2( 'L', 'N', 0, 0, -1, a, 1, x, af, 1, w, info )
247 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
248 infot = 5
249 CALL cunml2( 'L', 'N', 0, 1, 1, a, 1, x, af, 1, w, info )
250 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
251 infot = 5
252 CALL cunml2( 'R', 'N', 1, 0, 1, a, 1, x, af, 1, w, info )
253 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
254 infot = 7
255 CALL cunml2( 'L', 'N', 2, 1, 2, a, 1, x, af, 2, w, info )
256 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
257 infot = 7
258 CALL cunml2( 'R', 'N', 1, 2, 2, a, 1, x, af, 1, w, info )
259 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
260 infot = 10
261 CALL cunml2( 'L', 'N', 2, 1, 0, a, 2, x, af, 1, w, info )
262 CALL chkxer( 'CUNML2', infot, nout, lerr, ok )
263*
264* Print a summary line.
265*
266 CALL alaesm( path, ok, nout )
267*
268 RETURN
269*
270* End of CERRLQ
271*
272 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine cerrlq(path, nunit)
CERRLQ
Definition cerrlq.f:55
subroutine cgelq2(m, n, a, lda, tau, work, info)
CGELQ2 computes the LQ factorization of a general rectangular matrix using an unblocked algorithm.
Definition cgelq2.f:129
subroutine cgelqf(m, n, a, lda, tau, work, lwork, info)
CGELQF
Definition cgelqf.f:143
subroutine cungl2(m, n, k, a, lda, tau, work, info)
CUNGL2 generates all or part of the unitary matrix Q from an LQ factorization determined by cgelqf (u...
Definition cungl2.f:113
subroutine cunglq(m, n, k, a, lda, tau, work, lwork, info)
CUNGLQ
Definition cunglq.f:127
subroutine cunml2(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
CUNML2 multiplies a general matrix by the unitary matrix from a LQ factorization determined by cgelqf...
Definition cunml2.f:159
subroutine cunmlq(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
CUNMLQ
Definition cunmlq.f:168