OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
serrlq.f
Go to the documentation of this file.
1*> \brief \b SERRLQ
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 SERRLQ( 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*> SERRLQ tests the error exits for the REAL 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 single_lin
52*
53* =====================================================================
54 SUBROUTINE serrlq( 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 REAL A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
76 $ W( NMAX ), X( NMAX )
77* ..
78* .. External Subroutines ..
79 EXTERNAL alaesm, chkxer, sgelq2, sgelqf, sgelqs, sorgl2,
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 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 ) = 1. / real( i+j )
104 af( 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* SGELQF
115*
116 srnamt = 'SGELQF'
117 infot = 1
118 CALL sgelqf( -1, 0, a, 1, b, w, 1, info )
119 CALL chkxer( 'SGELQF', infot, nout, lerr, ok )
120 infot = 2
121 CALL sgelqf( 0, -1, a, 1, b, w, 1, info )
122 CALL chkxer( 'SGELQF', infot, nout, lerr, ok )
123 infot = 4
124 CALL sgelqf( 2, 1, a, 1, b, w, 2, info )
125 CALL chkxer( 'SGELQF', infot, nout, lerr, ok )
126 infot = 7
127 CALL sgelqf( 2, 1, a, 2, b, w, 1, info )
128 CALL chkxer( 'SGELQF', infot, nout, lerr, ok )
129*
130* SGELQ2
131*
132 srnamt = 'SGELQ2'
133 infot = 1
134 CALL sgelq2( -1, 0, a, 1, b, w, info )
135 CALL chkxer( 'SGELQ2', infot, nout, lerr, ok )
136 infot = 2
137 CALL sgelq2( 0, -1, a, 1, b, w, info )
138 CALL chkxer( 'SGELQ2', infot, nout, lerr, ok )
139 infot = 4
140 CALL sgelq2( 2, 1, a, 1, b, w, info )
141 CALL chkxer( 'SGELQ2', infot, nout, lerr, ok )
142*
143* SGELQS
144*
145 srnamt = 'SGELQS'
146 infot = 1
147 CALL sgelqs( -1, 0, 0, a, 1, x, b, 1, w, 1, info )
148 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
149 infot = 2
150 CALL sgelqs( 0, -1, 0, a, 1, x, b, 1, w, 1, info )
151 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
152 infot = 2
153 CALL sgelqs( 2, 1, 0, a, 2, x, b, 1, w, 1, info )
154 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
155 infot = 3
156 CALL sgelqs( 0, 0, -1, a, 1, x, b, 1, w, 1, info )
157 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
158 infot = 5
159 CALL sgelqs( 2, 2, 0, a, 1, x, b, 2, w, 1, info )
160 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
161 infot = 8
162 CALL sgelqs( 1, 2, 0, a, 1, x, b, 1, w, 1, info )
163 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
164 infot = 10
165 CALL sgelqs( 1, 1, 2, a, 1, x, b, 1, w, 1, info )
166 CALL chkxer( 'SGELQS', infot, nout, lerr, ok )
167*
168* SORGLQ
169*
170 srnamt = 'sorglq'
171 INFOT = 1
172 CALL SORGLQ( -1, 0, 0, A, 1, X, W, 1, INFO )
173 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
174 INFOT = 2
175 CALL SORGLQ( 0, -1, 0, A, 1, X, W, 1, INFO )
176 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
177 INFOT = 2
178 CALL SORGLQ( 2, 1, 0, A, 2, X, W, 2, INFO )
179 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
180 INFOT = 3
181 CALL SORGLQ( 0, 0, -1, A, 1, X, W, 1, INFO )
182 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
183 INFOT = 3
184 CALL SORGLQ( 1, 1, 2, A, 1, X, W, 1, INFO )
185 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
186 INFOT = 5
187 CALL SORGLQ( 2, 2, 0, A, 1, X, W, 2, INFO )
188 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
189 INFOT = 8
190 CALL SORGLQ( 2, 2, 0, A, 2, X, W, 1, INFO )
191 CALL CHKXER( 'sorglq', INFOT, NOUT, LERR, OK )
192*
193* SORGL2
194*
195 SRNAMT = 'sorgl2'
196 INFOT = 1
197 CALL SORGL2( -1, 0, 0, A, 1, X, W, INFO )
198 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
199 INFOT = 2
200 CALL SORGL2( 0, -1, 0, A, 1, X, W, INFO )
201 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
202 INFOT = 2
203 CALL SORGL2( 2, 1, 0, A, 2, X, W, INFO )
204 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
205 INFOT = 3
206 CALL SORGL2( 0, 0, -1, A, 1, X, W, INFO )
207 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
208 INFOT = 3
209 CALL SORGL2( 1, 1, 2, A, 1, X, W, INFO )
210 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
211 INFOT = 5
212 CALL SORGL2( 2, 2, 0, A, 1, X, W, INFO )
213 CALL CHKXER( 'sorgl2', INFOT, NOUT, LERR, OK )
214*
215* SORMLQ
216*
217 SRNAMT = 'sormlq'
218 INFOT = 1
219 CALL SORMLQ( '/', 'n', 0, 0, 0, A, 1, X, AF, 1, W, 1, INFO )
220 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
221 INFOT = 2
222 CALL SORMLQ( 'l', '/', 0, 0, 0, a, 1, x, af, 1, w, 1, info )
223 CALL chkxer( 'SORMLQ', infot, nout, lerr, ok )
224 infot = 3
225 CALL sormlq( 'L', 'N', -1, 0, 0, a, 1, x, af, 1, w, 1, info )
226 CALL chkxer( 'SORMLQ', infot, nout, lerr, ok )
227 infot = 4
228 CALL sormlq( 'L', 'N', 0, -1, 0, a, 1, x, af, 1, w, 1, info )
229 CALL chkxer( 'sormlq', INFOT, NOUT, LERR, OK )
230 INFOT = 5
231 CALL SORMLQ( 'l', 'n', 0, 0, -1, A, 1, X, AF, 1, W, 1, INFO )
232 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
233 INFOT = 5
234 CALL SORMLQ( 'l', 'n', 0, 1, 1, A, 1, X, AF, 1, W, 1, INFO )
235 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
236 INFOT = 5
237 CALL SORMLQ( 'r', 'n', 1, 0, 1, A, 1, X, AF, 1, W, 1, INFO )
238 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
239 INFOT = 7
240 CALL SORMLQ( 'l', 'n', 2, 0, 2, A, 1, X, AF, 2, W, 1, INFO )
241 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
242 INFOT = 7
243 CALL SORMLQ( 'r', 'n', 0, 2, 2, A, 1, X, AF, 1, W, 1, INFO )
244 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
245 INFOT = 10
246 CALL SORMLQ( 'l', 'n', 2, 1, 0, A, 2, X, AF, 1, W, 1, INFO )
247 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
248 INFOT = 12
249 CALL SORMLQ( 'l', 'n', 1, 2, 0, A, 1, X, AF, 1, W, 1, INFO )
250 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
251 INFOT = 12
252 CALL SORMLQ( 'r', 'n', 2, 1, 0, A, 1, X, AF, 2, W, 1, INFO )
253 CALL CHKXER( 'sormlq', INFOT, NOUT, LERR, OK )
254*
255* SORML2
256*
257 SRNAMT = 'sorml2'
258 INFOT = 1
259 CALL SORML2( '/', 'n', 0, 0, 0, A, 1, X, AF, 1, W, INFO )
260 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
261 INFOT = 2
262 CALL SORML2( 'l', '/', 0, 0, 0, A, 1, X, AF, 1, W, INFO )
263 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
264 INFOT = 3
265 CALL SORML2( 'l', 'n', -1, 0, 0, A, 1, X, AF, 1, W, INFO )
266 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
267 INFOT = 4
268 CALL SORML2( 'l', 'n', 0, -1, 0, A, 1, X, AF, 1, W, INFO )
269 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
270 INFOT = 5
271 CALL SORML2( 'l', 'n', 0, 0, -1, A, 1, X, AF, 1, W, INFO )
272 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
273 INFOT = 5
274 CALL SORML2( 'l', 'n', 0, 1, 1, A, 1, X, AF, 1, W, INFO )
275 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
276 INFOT = 5
277 CALL SORML2( 'r', 'n', 1, 0, 1, A, 1, X, AF, 1, W, INFO )
278 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
279 INFOT = 7
280 CALL SORML2( 'l', 'n', 2, 1, 2, A, 1, X, AF, 2, W, INFO )
281 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
282 INFOT = 7
283 CALL SORML2( 'r', 'n', 1, 2, 2, A, 1, X, AF, 1, W, INFO )
284 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
285 INFOT = 10
286 CALL SORML2( 'l', 'n', 2, 1, 0, A, 2, X, AF, 1, W, INFO )
287 CALL CHKXER( 'sorml2', INFOT, NOUT, LERR, OK )
288*
289* Print a summary line.
290*
291 CALL ALAESM( PATH, OK, NOUT )
292*
293 RETURN
294*
295* End of SERRLQ
296*
297 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine sgelqf(m, n, a, lda, tau, work, lwork, info)
SGELQF
Definition sgelqf.f:143
subroutine sgelq2(m, n, a, lda, tau, work, info)
SGELQ2 computes the LQ factorization of a general rectangular matrix using an unblocked algorithm.
Definition sgelq2.f:129
subroutine sorml2(side, trans, m, n, k, a, lda, tau, c, ldc, work, info)
SORML2 multiplies a general matrix by the orthogonal matrix from a LQ factorization determined by sge...
Definition sorml2.f:159
subroutine sorglq(m, n, k, a, lda, tau, work, lwork, info)
SORGLQ
Definition sorglq.f:127
subroutine sormlq(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
SORMLQ
Definition sormlq.f:168
subroutine sorgl2(m, n, k, a, lda, tau, work, info)
SORGL2
Definition sorgl2.f:113
subroutine serrlq(path, nunit)
SERRLQ
Definition serrlq.f:55
subroutine sgelqs(m, n, nrhs, a, lda, tau, b, ldb, work, lwork, info)
SGELQS
Definition sgelqs.f:121