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

CUNT03

Purpose:
 CUNT03 compares two unitary 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 abs(S) = 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 CUNT03 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 CUNT03 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
          CUNT03 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 COMPLEX 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 COMPLEX 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 COMPLEX 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]RWORK
          RWORK is REAL array, dimension (max(MV,N))
[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.
Date
November 2011

Definition at line 164 of file cunt03.f.

164 *
165 * -- LAPACK test routine (version 3.4.0) --
166 * -- LAPACK is a software package provided by Univ. of Tennessee, --
167 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * November 2011
169 *
170 * .. Scalar Arguments ..
171  CHARACTER*( * ) rc
172  INTEGER info, k, ldu, ldv, lwork, mu, mv, n
173  REAL result
174 * ..
175 * .. Array Arguments ..
176  REAL rwork( * )
177  COMPLEX u( ldu, * ), v( ldv, * ), work( * )
178 * ..
179 *
180 * =====================================================================
181 *
182 *
183 * .. Parameters ..
184  REAL zero, one
185  parameter ( zero = 0.0e0, one = 1.0e0 )
186 * ..
187 * .. Local Scalars ..
188  INTEGER i, irc, j, lmx
189  REAL res1, res2, ulp
190  COMPLEX s, su, sv
191 * ..
192 * .. External Functions ..
193  LOGICAL lsame
194  INTEGER icamax
195  REAL slamch
196  EXTERNAL lsame, icamax, slamch
197 * ..
198 * .. Intrinsic Functions ..
199  INTRINSIC abs, cmplx, max, min, real
200 * ..
201 * .. External Subroutines ..
202  EXTERNAL cunt01, xerbla
203 * ..
204 * .. Executable Statements ..
205 *
206 * Check inputs
207 *
208  info = 0
209  IF( lsame( rc, 'R' ) ) THEN
210  irc = 0
211  ELSE IF( lsame( rc, 'C' ) ) THEN
212  irc = 1
213  ELSE
214  irc = -1
215  END IF
216  IF( irc.EQ.-1 ) THEN
217  info = -1
218  ELSE IF( mu.LT.0 ) THEN
219  info = -2
220  ELSE IF( mv.LT.0 ) THEN
221  info = -3
222  ELSE IF( n.LT.0 ) THEN
223  info = -4
224  ELSE IF( k.LT.0 .OR. k.GT.max( mu, mv ) ) THEN
225  info = -5
226  ELSE IF( ( irc.EQ.0 .AND. ldu.LT.max( 1, mu ) ) .OR.
227  $ ( irc.EQ.1 .AND. ldu.LT.max( 1, n ) ) ) THEN
228  info = -7
229  ELSE IF( ( irc.EQ.0 .AND. ldv.LT.max( 1, mv ) ) .OR.
230  $ ( irc.EQ.1 .AND. ldv.LT.max( 1, n ) ) ) THEN
231  info = -9
232  END IF
233  IF( info.NE.0 ) THEN
234  CALL xerbla( 'CUNT03', -info )
235  RETURN
236  END IF
237 *
238 * Initialize result
239 *
240  result = zero
241  IF( mu.EQ.0 .OR. mv.EQ.0 .OR. n.EQ.0 )
242  $ RETURN
243 *
244 * Machine constants
245 *
246  ulp = slamch( 'Precision' )
247 *
248  IF( irc.EQ.0 ) THEN
249 *
250 * Compare rows
251 *
252  res1 = zero
253  DO 20 i = 1, k
254  lmx = icamax( n, u( i, 1 ), ldu )
255  IF( v( i, lmx ).EQ.cmplx( zero ) ) THEN
256  sv = one
257  ELSE
258  sv = abs( v( i, lmx ) ) / v( i, lmx )
259  END IF
260  IF( u( i, lmx ).EQ.cmplx( zero ) ) THEN
261  su = one
262  ELSE
263  su = abs( u( i, lmx ) ) / u( i, lmx )
264  END IF
265  s = sv / su
266  DO 10 j = 1, n
267  res1 = max( res1, abs( u( i, j )-s*v( i, j ) ) )
268  10 CONTINUE
269  20 CONTINUE
270  res1 = res1 / ( REAL( n )*ulp )
271 *
272 * Compute orthogonality of rows of V.
273 *
274  CALL cunt01( 'Rows', mv, n, v, ldv, work, lwork, rwork, res2 )
275 *
276  ELSE
277 *
278 * Compare columns
279 *
280  res1 = zero
281  DO 40 i = 1, k
282  lmx = icamax( n, u( 1, i ), 1 )
283  IF( v( lmx, i ).EQ.cmplx( zero ) ) THEN
284  sv = one
285  ELSE
286  sv = abs( v( lmx, i ) ) / v( lmx, i )
287  END IF
288  IF( u( lmx, i ).EQ.cmplx( zero ) ) THEN
289  su = one
290  ELSE
291  su = abs( u( lmx, i ) ) / u( lmx, i )
292  END IF
293  s = sv / su
294  DO 30 j = 1, n
295  res1 = max( res1, abs( u( j, i )-s*v( j, i ) ) )
296  30 CONTINUE
297  40 CONTINUE
298  res1 = res1 / ( REAL( n )*ulp )
299 *
300 * Compute orthogonality of columns of V.
301 *
302  CALL cunt01( 'Columns', n, mv, v, ldv, work, lwork, rwork,
303  $ res2 )
304  END IF
305 *
306  result = min( max( res1, res2 ), one / ulp )
307  RETURN
308 *
309 * End of CUNT03
310 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
integer function icamax(N, CX, INCX)
ICAMAX
Definition: icamax.f:53
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine cunt01(ROWCOL, M, N, U, LDU, WORK, LWORK, RWORK, RESID)
CUNT01
Definition: cunt01.f:128

Here is the call graph for this function:

Here is the caller graph for this function: