LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sort03()

subroutine sort03 ( character*( * )  rc,
integer  mu,
integer  mv,
integer  n,
integer  k,
real, dimension( ldu, * )  u,
integer  ldu,
real, dimension( ldv, * )  v,
integer  ldv,
real, dimension( * )  work,
integer  lwork,
real  result,
integer  info 
)

SORT03

Purpose:
 SORT03 compares two orthogonal matrices U and V to see if their
 corresponding rows or columns span the same spaces.  The rows are
 checked if RC = 'R', and the columns are checked if RC = 'C'.

 RESULT is the maximum of

    | V*V' - I | / ( MV ulp ), if RC = 'R', or

    | V'*V - I | / ( MV ulp ), if RC = 'C',

 and the maximum over rows (or columns) 1 to K of

    | U(i) - S*V(i) |/ ( N ulp )

 where S is +-1 (chosen to minimize the expression), U(i) is the i-th
 row (column) of U, and V(i) is the i-th row (column) of V.
Parameters
[in]RC
          RC is CHARACTER*1
          If RC = 'R' the rows of U and V are to be compared.
          If RC = 'C' the columns of U and V are to be compared.
[in]MU
          MU is INTEGER
          The number of rows of U if RC = 'R', and the number of
          columns if RC = 'C'.  If MU = 0 SORT03 does nothing.
          MU must be at least zero.
[in]MV
          MV is INTEGER
          The number of rows of V if RC = 'R', and the number of
          columns if RC = 'C'.  If MV = 0 SORT03 does nothing.
          MV must be at least zero.
[in]N
          N is INTEGER
          If RC = 'R', the number of columns in the matrices U and V,
          and if RC = 'C', the number of rows in U and V.  If N = 0
          SORT03 does nothing.  N must be at least zero.
[in]K
          K is INTEGER
          The number of rows or columns of U and V to compare.
          0 <= K <= max(MU,MV).
[in]U
          U is REAL array, dimension (LDU,N)
          The first matrix to compare.  If RC = 'R', U is MU by N, and
          if RC = 'C', U is N by MU.
[in]LDU
          LDU is INTEGER
          The leading dimension of U.  If RC = 'R', LDU >= max(1,MU),
          and if RC = 'C', LDU >= max(1,N).
[in]V
          V is REAL array, dimension (LDV,N)
          The second matrix to compare.  If RC = 'R', V is MV by N, and
          if RC = 'C', V is N by MV.
[in]LDV
          LDV is INTEGER
          The leading dimension of V.  If RC = 'R', LDV >= max(1,MV),
          and if RC = 'C', LDV >= max(1,N).
[out]WORK
          WORK is REAL array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The length of the array WORK.  For best performance, LWORK
          should be at least N*N if RC = 'C' or M*M if RC = 'R', but
          the tests will be done even if LWORK is 0.
[out]RESULT
          RESULT is REAL
          The value computed by the test described above.  RESULT is
          limited to 1/ulp to avoid overflow.
[out]INFO
          INFO is INTEGER
          0  indicates a successful exit
          -k indicates the k-th parameter had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 154 of file sort03.f.

156*
157* -- LAPACK test routine --
158* -- LAPACK is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 CHARACTER*( * ) RC
163 INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
164 REAL RESULT
165* ..
166* .. Array Arguments ..
167 REAL U( LDU, * ), V( LDV, * ), WORK( * )
168* ..
169*
170* =====================================================================
171*
172* .. Parameters ..
173 REAL ZERO, ONE
174 parameter( zero = 0.0e0, one = 1.0e0 )
175* ..
176* .. Local Scalars ..
177 INTEGER I, IRC, J, LMX
178 REAL RES1, RES2, S, ULP
179* ..
180* .. External Functions ..
181 LOGICAL LSAME
182 INTEGER ISAMAX
183 REAL SLAMCH
184 EXTERNAL lsame, isamax, slamch
185* ..
186* .. Intrinsic Functions ..
187 INTRINSIC abs, max, min, real, sign
188* ..
189* .. External Subroutines ..
190 EXTERNAL sort01, xerbla
191* ..
192* .. Executable Statements ..
193*
194* Check inputs
195*
196 info = 0
197 IF( lsame( rc, 'R' ) ) THEN
198 irc = 0
199 ELSE IF( lsame( rc, 'C' ) ) THEN
200 irc = 1
201 ELSE
202 irc = -1
203 END IF
204 IF( irc.EQ.-1 ) THEN
205 info = -1
206 ELSE IF( mu.LT.0 ) THEN
207 info = -2
208 ELSE IF( mv.LT.0 ) THEN
209 info = -3
210 ELSE IF( n.LT.0 ) THEN
211 info = -4
212 ELSE IF( k.LT.0 .OR. k.GT.max( mu, mv ) ) THEN
213 info = -5
214 ELSE IF( ( irc.EQ.0 .AND. ldu.LT.max( 1, mu ) ) .OR.
215 $ ( irc.EQ.1 .AND. ldu.LT.max( 1, n ) ) ) THEN
216 info = -7
217 ELSE IF( ( irc.EQ.0 .AND. ldv.LT.max( 1, mv ) ) .OR.
218 $ ( irc.EQ.1 .AND. ldv.LT.max( 1, n ) ) ) THEN
219 info = -9
220 END IF
221 IF( info.NE.0 ) THEN
222 CALL xerbla( 'SORT03', -info )
223 RETURN
224 END IF
225*
226* Initialize result
227*
228 result = zero
229 IF( mu.EQ.0 .OR. mv.EQ.0 .OR. n.EQ.0 )
230 $ RETURN
231*
232* Machine constants
233*
234 ulp = slamch( 'Precision' )
235*
236 IF( irc.EQ.0 ) THEN
237*
238* Compare rows
239*
240 res1 = zero
241 DO 20 i = 1, k
242 lmx = isamax( n, u( i, 1 ), ldu )
243 s = sign( one, u( i, lmx ) )*sign( one, v( i, lmx ) )
244 DO 10 j = 1, n
245 res1 = max( res1, abs( u( i, j )-s*v( i, j ) ) )
246 10 CONTINUE
247 20 CONTINUE
248 res1 = res1 / ( real( n )*ulp )
249*
250* Compute orthogonality of rows of V.
251*
252 CALL sort01( 'Rows', mv, n, v, ldv, work, lwork, res2 )
253*
254 ELSE
255*
256* Compare columns
257*
258 res1 = zero
259 DO 40 i = 1, k
260 lmx = isamax( n, u( 1, i ), 1 )
261 s = sign( one, u( lmx, i ) )*sign( one, v( lmx, i ) )
262 DO 30 j = 1, n
263 res1 = max( res1, abs( u( j, i )-s*v( j, i ) ) )
264 30 CONTINUE
265 40 CONTINUE
266 res1 = res1 / ( real( n )*ulp )
267*
268* Compute orthogonality of columns of V.
269*
270 CALL sort01( 'Columns', n, mv, v, ldv, work, lwork, res2 )
271 END IF
272*
273 result = min( max( res1, res2 ), one / ulp )
274 RETURN
275*
276* End of SORT03
277*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function isamax(n, sx, incx)
ISAMAX
Definition isamax.f:71
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sort01(rowcol, m, n, u, ldu, work, lwork, resid)
SORT01
Definition sort01.f:116
Here is the call graph for this function:
Here is the caller graph for this function: