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

◆ zunt03()

subroutine zunt03 ( character*( * ) rc,
integer mu,
integer mv,
integer n,
integer k,
complex*16, dimension( ldu, * ) u,
integer ldu,
complex*16, dimension( ldv, * ) v,
integer ldv,
complex*16, dimension( * ) work,
integer lwork,
double precision, dimension( * ) rwork,
double precision result,
integer info )

ZUNT03

Purpose:
!>
!> ZUNT03 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 ZUNT03 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 ZUNT03 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
!>          ZUNT03 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*16 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*16 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*16 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 DOUBLE PRECISION array, dimension (max(MV,N))
!> 
[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.

Definition at line 160 of file zunt03.f.

162*
163* -- LAPACK test routine --
164* -- LAPACK is a software package provided by Univ. of Tennessee, --
165* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
166*
167* .. Scalar Arguments ..
168 CHARACTER*( * ) RC
169 INTEGER INFO, K, LDU, LDV, LWORK, MU, MV, N
170 DOUBLE PRECISION RESULT
171* ..
172* .. Array Arguments ..
173 DOUBLE PRECISION RWORK( * )
174 COMPLEX*16 U( LDU, * ), V( LDV, * ), WORK( * )
175* ..
176*
177* =====================================================================
178*
179*
180* .. Parameters ..
181 DOUBLE PRECISION ZERO, ONE
182 parameter( zero = 0.0d0, one = 1.0d0 )
183* ..
184* .. Local Scalars ..
185 INTEGER I, IRC, J, LMX
186 DOUBLE PRECISION RES1, RES2, ULP
187 COMPLEX*16 S, SU, SV
188* ..
189* .. External Functions ..
190 LOGICAL LSAME
191 INTEGER IZAMAX
192 DOUBLE PRECISION DLAMCH
193 EXTERNAL lsame, izamax, dlamch
194* ..
195* .. Intrinsic Functions ..
196 INTRINSIC abs, dble, dcmplx, max, min
197* ..
198* .. External Subroutines ..
199 EXTERNAL xerbla, zunt01
200* ..
201* .. Executable Statements ..
202*
203* Check inputs
204*
205 info = 0
206 IF( lsame( rc, 'R' ) ) THEN
207 irc = 0
208 ELSE IF( lsame( rc, 'C' ) ) THEN
209 irc = 1
210 ELSE
211 irc = -1
212 END IF
213 IF( irc.EQ.-1 ) THEN
214 info = -1
215 ELSE IF( mu.LT.0 ) THEN
216 info = -2
217 ELSE IF( mv.LT.0 ) THEN
218 info = -3
219 ELSE IF( n.LT.0 ) THEN
220 info = -4
221 ELSE IF( k.LT.0 .OR. k.GT.max( mu, mv ) ) THEN
222 info = -5
223 ELSE IF( ( irc.EQ.0 .AND. ldu.LT.max( 1, mu ) ) .OR.
224 $ ( irc.EQ.1 .AND. ldu.LT.max( 1, n ) ) ) THEN
225 info = -7
226 ELSE IF( ( irc.EQ.0 .AND. ldv.LT.max( 1, mv ) ) .OR.
227 $ ( irc.EQ.1 .AND. ldv.LT.max( 1, n ) ) ) THEN
228 info = -9
229 END IF
230 IF( info.NE.0 ) THEN
231 CALL xerbla( 'ZUNT03', -info )
232 RETURN
233 END IF
234*
235* Initialize result
236*
237 result = zero
238 IF( mu.EQ.0 .OR. mv.EQ.0 .OR. n.EQ.0 )
239 $ RETURN
240*
241* Machine constants
242*
243 ulp = dlamch( 'Precision' )
244*
245 IF( irc.EQ.0 ) THEN
246*
247* Compare rows
248*
249 res1 = zero
250 DO 20 i = 1, k
251 lmx = izamax( n, u( i, 1 ), ldu )
252 IF( v( i, lmx ).EQ.dcmplx( zero ) ) THEN
253 sv = one
254 ELSE
255 sv = abs( v( i, lmx ) ) / v( i, lmx )
256 END IF
257 IF( u( i, lmx ).EQ.dcmplx( zero ) ) THEN
258 su = one
259 ELSE
260 su = abs( u( i, lmx ) ) / u( i, lmx )
261 END IF
262 s = sv / su
263 DO 10 j = 1, n
264 res1 = max( res1, abs( u( i, j )-s*v( i, j ) ) )
265 10 CONTINUE
266 20 CONTINUE
267 res1 = res1 / ( dble( n )*ulp )
268*
269* Compute orthogonality of rows of V.
270*
271 CALL zunt01( 'Rows', mv, n, v, ldv, work, lwork, rwork, res2 )
272*
273 ELSE
274*
275* Compare columns
276*
277 res1 = zero
278 DO 40 i = 1, k
279 lmx = izamax( n, u( 1, i ), 1 )
280 IF( v( lmx, i ).EQ.dcmplx( zero ) ) THEN
281 sv = one
282 ELSE
283 sv = abs( v( lmx, i ) ) / v( lmx, i )
284 END IF
285 IF( u( lmx, i ).EQ.dcmplx( zero ) ) THEN
286 su = one
287 ELSE
288 su = abs( u( lmx, i ) ) / u( lmx, i )
289 END IF
290 s = sv / su
291 DO 30 j = 1, n
292 res1 = max( res1, abs( u( j, i )-s*v( j, i ) ) )
293 30 CONTINUE
294 40 CONTINUE
295 res1 = res1 / ( dble( n )*ulp )
296*
297* Compute orthogonality of columns of V.
298*
299 CALL zunt01( 'Columns', n, mv, v, ldv, work, lwork, rwork,
300 $ res2 )
301 END IF
302*
303 result = min( max( res1, res2 ), one / ulp )
304 RETURN
305*
306* End of ZUNT03
307*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function izamax(n, zx, incx)
IZAMAX
Definition izamax.f:71
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zunt01(rowcol, m, n, u, ldu, work, lwork, rwork, resid)
ZUNT01
Definition zunt01.f:126
Here is the call graph for this function:
Here is the caller graph for this function: