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

◆ cunt01()

subroutine cunt01 ( character  rowcol,
integer  m,
integer  n,
complex, dimension( ldu, * )  u,
integer  ldu,
complex, dimension( * )  work,
integer  lwork,
real, dimension( * )  rwork,
real  resid 
)

CUNT01

Purpose:
 CUNT01 checks that the matrix U is unitary by computing the ratio

    RESID = norm( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
 or
    RESID = norm( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.

 Alternatively, if there isn't sufficient workspace to form
 I - U*U' or I - U'*U, the ratio is computed as

    RESID = abs( I - U*U' ) / ( n * EPS ), if ROWCOL = 'R',
 or
    RESID = abs( I - U'*U ) / ( m * EPS ), if ROWCOL = 'C'.

 where EPS is the machine precision.  ROWCOL is used only if m = n;
 if m > n, ROWCOL is assumed to be 'C', and if m < n, ROWCOL is
 assumed to be 'R'.
Parameters
[in]ROWCOL
          ROWCOL is CHARACTER
          Specifies whether the rows or columns of U should be checked
          for orthogonality.  Used only if M = N.
          = 'R':  Check for orthogonal rows of U
          = 'C':  Check for orthogonal columns of U
[in]M
          M is INTEGER
          The number of rows of the matrix U.
[in]N
          N is INTEGER
          The number of columns of the matrix U.
[in]U
          U is COMPLEX array, dimension (LDU,N)
          The unitary matrix U.  U is checked for orthogonal columns
          if m > n or if m = n and ROWCOL = 'C'.  U is checked for
          orthogonal rows if m < n or if m = n and ROWCOL = 'R'.
[in]LDU
          LDU is INTEGER
          The leading dimension of the array U.  LDU >= max(1,M).
[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 ROWCOL = 'C' or M*M if
          ROWCOL = 'R', but the test will be done even if LWORK is 0.
[out]RWORK
          RWORK is REAL array, dimension (min(M,N))
          Used only if LWORK is large enough to use the Level 3 BLAS
          code.
[out]RESID
          RESID is REAL
          RESID = norm( I - U * U' ) / ( n * EPS ), if ROWCOL = 'R', or
          RESID = norm( I - U' * U ) / ( m * EPS ), if ROWCOL = 'C'.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 124 of file cunt01.f.

126*
127* -- LAPACK test routine --
128* -- LAPACK is a software package provided by Univ. of Tennessee, --
129* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130*
131* .. Scalar Arguments ..
132 CHARACTER ROWCOL
133 INTEGER LDU, LWORK, M, N
134 REAL RESID
135* ..
136* .. Array Arguments ..
137 REAL RWORK( * )
138 COMPLEX U( LDU, * ), WORK( * )
139* ..
140*
141* =====================================================================
142*
143* .. Parameters ..
144 REAL ZERO, ONE
145 parameter( zero = 0.0e+0, one = 1.0e+0 )
146* ..
147* .. Local Scalars ..
148 CHARACTER TRANSU
149 INTEGER I, J, K, LDWORK, MNMIN
150 REAL EPS
151 COMPLEX TMP, ZDUM
152* ..
153* .. External Functions ..
154 LOGICAL LSAME
155 REAL CLANSY, SLAMCH
156 COMPLEX CDOTC
157 EXTERNAL lsame, clansy, slamch, cdotc
158* ..
159* .. External Subroutines ..
160 EXTERNAL cherk, claset
161* ..
162* .. Intrinsic Functions ..
163 INTRINSIC abs, aimag, cmplx, max, min, real
164* ..
165* .. Statement Functions ..
166 REAL CABS1
167* ..
168* .. Statement Function definitions ..
169 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
170* ..
171* .. Executable Statements ..
172*
173 resid = zero
174*
175* Quick return if possible
176*
177 IF( m.LE.0 .OR. n.LE.0 )
178 $ RETURN
179*
180 eps = slamch( 'Precision' )
181 IF( m.LT.n .OR. ( m.EQ.n .AND. lsame( rowcol, 'R' ) ) ) THEN
182 transu = 'N'
183 k = n
184 ELSE
185 transu = 'C'
186 k = m
187 END IF
188 mnmin = min( m, n )
189*
190 IF( ( mnmin+1 )*mnmin.LE.lwork ) THEN
191 ldwork = mnmin
192 ELSE
193 ldwork = 0
194 END IF
195 IF( ldwork.GT.0 ) THEN
196*
197* Compute I - U*U' or I - U'*U.
198*
199 CALL claset( 'Upper', mnmin, mnmin, cmplx( zero ),
200 $ cmplx( one ), work, ldwork )
201 CALL cherk( 'Upper', transu, mnmin, k, -one, u, ldu, one, work,
202 $ ldwork )
203*
204* Compute norm( I - U*U' ) / ( K * EPS ) .
205*
206 resid = clansy( '1', 'Upper', mnmin, work, ldwork, rwork )
207 resid = ( resid / real( k ) ) / eps
208 ELSE IF( transu.EQ.'C' ) THEN
209*
210* Find the maximum element in abs( I - U'*U ) / ( m * EPS )
211*
212 DO 20 j = 1, n
213 DO 10 i = 1, j
214 IF( i.NE.j ) THEN
215 tmp = zero
216 ELSE
217 tmp = one
218 END IF
219 tmp = tmp - cdotc( m, u( 1, i ), 1, u( 1, j ), 1 )
220 resid = max( resid, cabs1( tmp ) )
221 10 CONTINUE
222 20 CONTINUE
223 resid = ( resid / real( m ) ) / eps
224 ELSE
225*
226* Find the maximum element in abs( I - U*U' ) / ( n * EPS )
227*
228 DO 40 j = 1, m
229 DO 30 i = 1, j
230 IF( i.NE.j ) THEN
231 tmp = zero
232 ELSE
233 tmp = one
234 END IF
235 tmp = tmp - cdotc( n, u( j, 1 ), ldu, u( i, 1 ), ldu )
236 resid = max( resid, cabs1( tmp ) )
237 30 CONTINUE
238 40 CONTINUE
239 resid = ( resid / real( n ) ) / eps
240 END IF
241 RETURN
242*
243* End of CUNT01
244*
complex function cdotc(n, cx, incx, cy, incy)
CDOTC
Definition cdotc.f:83
subroutine cherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
CHERK
Definition cherk.f:173
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function clansy(norm, uplo, n, a, lda, work)
CLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition clansy.f:123
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition claset.f:106
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: