LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zerrrq.f
Go to the documentation of this file.
1*> \brief \b ZERRRQ
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 ZERRRQ( 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*> ZERRRQ tests the error exits for the COMPLEX*16 routines
25*> that use the RQ 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 complex16_lin
52*
53* =====================================================================
54 SUBROUTINE zerrrq( 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*16 A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
76 $ W( NMAX ), X( NMAX )
77* ..
78* .. External Subroutines ..
79 EXTERNAL alaesm, chkxer, zgerq2, zgerqf, zgerqs, zungr2,
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 dble, dcmplx
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 ) = dcmplx( 1.d0 / dble( i+j ),
104 $ -1.d0 / dble( i+j ) )
105 af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
106 $ -1.d0 / dble( i+j ) )
107 10 CONTINUE
108 b( j ) = 0.d0
109 w( j ) = 0.d0
110 x( j ) = 0.d0
111 20 CONTINUE
112 ok = .true.
113*
114* Error exits for RQ factorization
115*
116* ZGERQF
117*
118 srnamt = 'ZGERQF'
119 infot = 1
120 CALL zgerqf( -1, 0, a, 1, b, w, 1, info )
121 CALL chkxer( 'ZGERQF', infot, nout, lerr, ok )
122 infot = 2
123 CALL zgerqf( 0, -1, a, 1, b, w, 1, info )
124 CALL chkxer( 'ZGERQF', infot, nout, lerr, ok )
125 infot = 4
126 CALL zgerqf( 2, 1, a, 1, b, w, 2, info )
127 CALL chkxer( 'ZGERQF', infot, nout, lerr, ok )
128 infot = 7
129 CALL zgerqf( 2, 1, a, 2, b, w, 1, info )
130 CALL chkxer( 'ZGERQF', infot, nout, lerr, ok )
131*
132* ZGERQ2
133*
134 srnamt = 'ZGERQ2'
135 infot = 1
136 CALL zgerq2( -1, 0, a, 1, b, w, info )
137 CALL chkxer( 'ZGERQ2', infot, nout, lerr, ok )
138 infot = 2
139 CALL zgerq2( 0, -1, a, 1, b, w, info )
140 CALL chkxer( 'ZGERQ2', infot, nout, lerr, ok )
141 infot = 4
142 CALL zgerq2( 2, 1, a, 1, b, w, info )
143 CALL chkxer( 'ZGERQ2', infot, nout, lerr, ok )
144*
145* ZGERQS
146*
147 srnamt = 'ZGERQS'
148 infot = 1
149 CALL zgerqs( -1, 0, 0, a, 1, x, b, 1, w, 1, info )
150 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
151 infot = 2
152 CALL zgerqs( 0, -1, 0, a, 1, x, b, 1, w, 1, info )
153 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
154 infot = 2
155 CALL zgerqs( 2, 1, 0, a, 2, x, b, 1, w, 1, info )
156 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
157 infot = 3
158 CALL zgerqs( 0, 0, -1, a, 1, x, b, 1, w, 1, info )
159 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
160 infot = 5
161 CALL zgerqs( 2, 2, 0, a, 1, x, b, 2, w, 1, info )
162 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
163 infot = 8
164 CALL zgerqs( 2, 2, 0, a, 2, x, b, 1, w, 1, info )
165 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
166 infot = 10
167 CALL zgerqs( 1, 1, 2, a, 1, x, b, 1, w, 1, info )
168 CALL chkxer( 'ZGERQS', infot, nout, lerr, ok )
169*
170* ZUNGRQ
171*
172 srnamt = 'ZUNGRQ'
173 infot = 1
174 CALL zungrq( -1, 0, 0, a, 1, x, w, 1, info )
175 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
176 infot = 2
177 CALL zungrq( 0, -1, 0, a, 1, x, w, 1, info )
178 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
179 infot = 2
180 CALL zungrq( 2, 1, 0, a, 2, x, w, 2, info )
181 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
182 infot = 3
183 CALL zungrq( 0, 0, -1, a, 1, x, w, 1, info )
184 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
185 infot = 3
186 CALL zungrq( 1, 2, 2, a, 1, x, w, 1, info )
187 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
188 infot = 5
189 CALL zungrq( 2, 2, 0, a, 1, x, w, 2, info )
190 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
191 infot = 8
192 CALL zungrq( 2, 2, 0, a, 2, x, w, 1, info )
193 CALL chkxer( 'ZUNGRQ', infot, nout, lerr, ok )
194*
195* ZUNGR2
196*
197 srnamt = 'ZUNGR2'
198 infot = 1
199 CALL zungr2( -1, 0, 0, a, 1, x, w, info )
200 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
201 infot = 2
202 CALL zungr2( 0, -1, 0, a, 1, x, w, info )
203 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
204 infot = 2
205 CALL zungr2( 2, 1, 0, a, 2, x, w, info )
206 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
207 infot = 3
208 CALL zungr2( 0, 0, -1, a, 1, x, w, info )
209 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
210 infot = 3
211 CALL zungr2( 1, 2, 2, a, 2, x, w, info )
212 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
213 infot = 5
214 CALL zungr2( 2, 2, 0, a, 1, x, w, info )
215 CALL chkxer( 'ZUNGR2', infot, nout, lerr, ok )
216*
217* ZUNMRQ
218*
219 srnamt = 'ZUNMRQ'
220 infot = 1
221 CALL zunmrq( '/', 'N', 0, 0, 0, a, 1, x, af, 1, w, 1, info )
222 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
223 infot = 2
224 CALL zunmrq( 'L', '/', 0, 0, 0, a, 1, x, af, 1, w, 1, info )
225 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
226 infot = 3
227 CALL zunmrq( 'L', 'N', -1, 0, 0, a, 1, x, af, 1, w, 1, info )
228 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
229 infot = 4
230 CALL zunmrq( 'L', 'N', 0, -1, 0, a, 1, x, af, 1, w, 1, info )
231 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
232 infot = 5
233 CALL zunmrq( 'L', 'N', 0, 0, -1, a, 1, x, af, 1, w, 1, info )
234 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
235 infot = 5
236 CALL zunmrq( 'L', 'N', 0, 1, 1, a, 1, x, af, 1, w, 1, info )
237 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
238 infot = 5
239 CALL zunmrq( 'R', 'N', 1, 0, 1, a, 1, x, af, 1, w, 1, info )
240 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
241 infot = 7
242 CALL zunmrq( 'L', 'N', 2, 1, 2, a, 1, x, af, 2, w, 1, info )
243 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
244 infot = 7
245 CALL zunmrq( 'R', 'N', 1, 2, 2, a, 1, x, af, 1, w, 1, info )
246 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
247 infot = 10
248 CALL zunmrq( 'L', 'N', 2, 1, 0, a, 1, x, af, 1, w, 1, info )
249 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
250 infot = 12
251 CALL zunmrq( 'L', 'N', 1, 2, 0, a, 1, x, af, 1, w, 1, info )
252 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
253 infot = 12
254 CALL zunmrq( 'R', 'N', 2, 1, 0, a, 1, x, af, 2, w, 1, info )
255 CALL chkxer( 'ZUNMRQ', infot, nout, lerr, ok )
256*
257* ZUNMR2
258*
259 srnamt = 'ZUNMR2'
260 infot = 1
261 CALL zunmr2( '/', 'N', 0, 0, 0, a, 1, x, af, 1, w, info )
262 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
263 infot = 2
264 CALL zunmr2( 'L', '/', 0, 0, 0, a, 1, x, af, 1, w, info )
265 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
266 infot = 3
267 CALL zunmr2( 'L', 'N', -1, 0, 0, a, 1, x, af, 1, w, info )
268 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
269 infot = 4
270 CALL zunmr2( 'L', 'N', 0, -1, 0, a, 1, x, af, 1, w, info )
271 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
272 infot = 5
273 CALL zunmr2( 'L', 'N', 0, 0, -1, a, 1, x, af, 1, w, info )
274 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
275 infot = 5
276 CALL zunmr2( 'L', 'N', 0, 1, 1, a, 1, x, af, 1, w, info )
277 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
278 infot = 5
279 CALL zunmr2( 'R', 'N', 1, 0, 1, a, 1, x, af, 1, w, info )
280 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
281 infot = 7
282 CALL zunmr2( 'L', 'N', 2, 1, 2, a, 1, x, af, 2, w, info )
283 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
284 infot = 7
285 CALL zunmr2( 'R', 'N', 1, 2, 2, a, 1, x, af, 1, w, info )
286 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
287 infot = 10
288 CALL zunmr2( 'L', 'N', 2, 1, 0, a, 1, x, af, 1, w, info )
289 CALL chkxer( 'ZUNMR2', infot, nout, lerr, ok )
290*
291* Print a summary line.
292*
293 CALL alaesm( path, ok, nout )
294*
295 RETURN
296*
297* End of ZERRRQ
298*
299 END
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine zgerq2(m, n, a, lda, tau, work, info)
ZGERQ2 computes the RQ factorization of a general rectangular matrix using an unblocked algorithm.
Definition zgerq2.f:123
subroutine zgerqf(m, n, a, lda, tau, work, lwork, info)
ZGERQF
Definition zgerqf.f:139
subroutine zungr2(m, n, k, a, lda, tau, work, info)
ZUNGR2 generates all or part of the unitary matrix Q from an RQ factorization determined by cgerqf (u...
Definition zungr2.f:114
subroutine zungrq(m, n, k, a, lda, tau, work, lwork, info)
ZUNGRQ
Definition zungrq.f:128
subroutine zunmr2(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
ZUNMR2 multiplies a general matrix by the unitary matrix from a RQ factorization determined by cgerqf...
Definition zunmr2.f:159
subroutine zunmrq(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
ZUNMRQ
Definition zunmrq.f:167
subroutine zerrrq(path, nunit)
ZERRRQ
Definition zerrrq.f:55
subroutine zgerqs(m, n, nrhs, a, lda, tau, b, ldb, work, lwork, info)
ZGERQS
Definition zgerqs.f:122