LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dort03 ( character*( * )  RC,
integer  MU,
integer  MV,
integer  N,
integer  K,
double precision, dimension( ldu, * )  U,
integer  LDU,
double precision, dimension( ldv, * )  V,
integer  LDV,
double precision, dimension( * )  WORK,
integer  LWORK,
double precision  RESULT,
integer  INFO 
)

DORT03

Purpose:
 DORT03 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 DORT03 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 DORT03 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
          DORT03 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION
          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.
Date
November 2011

Definition at line 158 of file dort03.f.

158 *
159 * -- LAPACK test routine (version 3.4.0) --
160 * -- LAPACK is a software package provided by Univ. of Tennessee, --
161 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162 * November 2011
163 *
164 * .. Scalar Arguments ..
165  CHARACTER*( * ) rc
166  INTEGER info, k, ldu, ldv, lwork, mu, mv, n
167  DOUBLE PRECISION result
168 * ..
169 * .. Array Arguments ..
170  DOUBLE PRECISION u( ldu, * ), v( ldv, * ), work( * )
171 * ..
172 *
173 * =====================================================================
174 *
175 * .. Parameters ..
176  DOUBLE PRECISION zero, one
177  parameter ( zero = 0.0d0, one = 1.0d0 )
178 * ..
179 * .. Local Scalars ..
180  INTEGER i, irc, j, lmx
181  DOUBLE PRECISION res1, res2, s, ulp
182 * ..
183 * .. External Functions ..
184  LOGICAL lsame
185  INTEGER idamax
186  DOUBLE PRECISION dlamch
187  EXTERNAL lsame, idamax, dlamch
188 * ..
189 * .. Intrinsic Functions ..
190  INTRINSIC abs, dble, max, min, sign
191 * ..
192 * .. External Subroutines ..
193  EXTERNAL dort01, xerbla
194 * ..
195 * .. Executable Statements ..
196 *
197 * Check inputs
198 *
199  info = 0
200  IF( lsame( rc, 'R' ) ) THEN
201  irc = 0
202  ELSE IF( lsame( rc, 'C' ) ) THEN
203  irc = 1
204  ELSE
205  irc = -1
206  END IF
207  IF( irc.EQ.-1 ) THEN
208  info = -1
209  ELSE IF( mu.LT.0 ) THEN
210  info = -2
211  ELSE IF( mv.LT.0 ) THEN
212  info = -3
213  ELSE IF( n.LT.0 ) THEN
214  info = -4
215  ELSE IF( k.LT.0 .OR. k.GT.max( mu, mv ) ) THEN
216  info = -5
217  ELSE IF( ( irc.EQ.0 .AND. ldu.LT.max( 1, mu ) ) .OR.
218  $ ( irc.EQ.1 .AND. ldu.LT.max( 1, n ) ) ) THEN
219  info = -7
220  ELSE IF( ( irc.EQ.0 .AND. ldv.LT.max( 1, mv ) ) .OR.
221  $ ( irc.EQ.1 .AND. ldv.LT.max( 1, n ) ) ) THEN
222  info = -9
223  END IF
224  IF( info.NE.0 ) THEN
225  CALL xerbla( 'DORT03', -info )
226  RETURN
227  END IF
228 *
229 * Initialize result
230 *
231  result = zero
232  IF( mu.EQ.0 .OR. mv.EQ.0 .OR. n.EQ.0 )
233  $ RETURN
234 *
235 * Machine constants
236 *
237  ulp = dlamch( 'Precision' )
238 *
239  IF( irc.EQ.0 ) THEN
240 *
241 * Compare rows
242 *
243  res1 = zero
244  DO 20 i = 1, k
245  lmx = idamax( n, u( i, 1 ), ldu )
246  s = sign( one, u( i, lmx ) )*sign( one, v( i, lmx ) )
247  DO 10 j = 1, n
248  res1 = max( res1, abs( u( i, j )-s*v( i, j ) ) )
249  10 CONTINUE
250  20 CONTINUE
251  res1 = res1 / ( dble( n )*ulp )
252 *
253 * Compute orthogonality of rows of V.
254 *
255  CALL dort01( 'Rows', mv, n, v, ldv, work, lwork, res2 )
256 *
257  ELSE
258 *
259 * Compare columns
260 *
261  res1 = zero
262  DO 40 i = 1, k
263  lmx = idamax( n, u( 1, i ), 1 )
264  s = sign( one, u( lmx, i ) )*sign( one, v( lmx, i ) )
265  DO 30 j = 1, n
266  res1 = max( res1, abs( u( j, i )-s*v( j, i ) ) )
267  30 CONTINUE
268  40 CONTINUE
269  res1 = res1 / ( dble( n )*ulp )
270 *
271 * Compute orthogonality of columns of V.
272 *
273  CALL dort01( 'Columns', n, mv, v, ldv, work, lwork, res2 )
274  END IF
275 *
276  result = min( max( res1, res2 ), one / ulp )
277  RETURN
278 *
279 * End of DORT03
280 *
integer function idamax(N, DX, INCX)
IDAMAX
Definition: idamax.f:53
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dort01(ROWCOL, M, N, U, LDU, WORK, LWORK, RESID)
DORT01
Definition: dort01.f:118
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: