File: zunt03.f

package info (click to toggle)
lapack 3.0.20000531a-28
  • links: PTS
  • area: main
  • in suites: sarge
  • size: 61,920 kB
  • ctags: 46,200
  • sloc: fortran: 584,835; perl: 8,226; makefile: 2,331; awk: 71; sh: 45
file content (229 lines) | stat: -rw-r--r-- 6,870 bytes parent folder | download | duplicates (6)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
      SUBROUTINE ZUNT03( RC, MU, MV, N, K, U, LDU, V, LDV, WORK, LWORK,
     $                   RWORK, RESULT, INFO )
*
*  -- LAPACK test routine (version 3.0) --
*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
*     Courant Institute, Argonne National Lab, and Rice University
*     February 29, 1992
*
*     .. Scalar Arguments ..
      CHARACTER*( * )    RC
      INTEGER            INFO, K, LDU, LDV, LWORK, MU, MV, N
      DOUBLE PRECISION   RESULT
*     ..
*     .. Array Arguments ..
      DOUBLE PRECISION   RWORK( * )
      COMPLEX*16         U( LDU, * ), V( LDV, * ), WORK( * )
*     ..
*
*  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.
*
*  Arguments
*  ==========
*
*  RC      (input) 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.
*
*  MU      (input) 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.
*
*  MV      (input) 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.
*
*  N       (input) 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.
*
*  K       (input) INTEGER
*          The number of rows or columns of U and V to compare.
*          0 <= K <= max(MU,MV).
*
*  U       (input) 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.
*
*  LDU     (input) INTEGER
*          The leading dimension of U.  If RC = 'R', LDU >= max(1,MU),
*          and if RC = 'C', LDU >= max(1,N).
*
*  V       (input) 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.
*
*  LDV     (input) INTEGER
*          The leading dimension of V.  If RC = 'R', LDV >= max(1,MV),
*          and if RC = 'C', LDV >= max(1,N).
*
*  WORK    (workspace) COMPLEX*16 array, dimension (LWORK)
*
*  LWORK   (input) 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.
*
*  RWORK   (workspace) DOUBLE PRECISION array, dimension (max(MV,N))
*
*  RESULT  (output) DOUBLE PRECISION
*          The value computed by the test described above.  RESULT is
*          limited to 1/ulp to avoid overflow.
*
*  INFO    (output) INTEGER
*          0  indicates a successful exit
*          -k indicates the k-th parameter had an illegal value
*
*  =====================================================================
*
*
*     .. Parameters ..
      DOUBLE PRECISION   ZERO, ONE
      PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0 )
*     ..
*     .. Local Scalars ..
      INTEGER            I, IRC, J, LMX
      DOUBLE PRECISION   RES1, RES2, ULP
      COMPLEX*16         S, SU, SV
*     ..
*     .. External Functions ..
      LOGICAL            LSAME
      INTEGER            IZAMAX
      DOUBLE PRECISION   DLAMCH
      EXTERNAL           LSAME, IZAMAX, DLAMCH
*     ..
*     .. Intrinsic Functions ..
      INTRINSIC          ABS, DBLE, DCMPLX, MAX, MIN
*     ..
*     .. External Subroutines ..
      EXTERNAL           XERBLA, ZUNT01
*     ..
*     .. Executable Statements ..
*
*     Check inputs
*
      INFO = 0
      IF( LSAME( RC, 'R' ) ) THEN
         IRC = 0
      ELSE IF( LSAME( RC, 'C' ) ) THEN
         IRC = 1
      ELSE
         IRC = -1
      END IF
      IF( IRC.EQ.-1 ) THEN
         INFO = -1
      ELSE IF( MU.LT.0 ) THEN
         INFO = -2
      ELSE IF( MV.LT.0 ) THEN
         INFO = -3
      ELSE IF( N.LT.0 ) THEN
         INFO = -4
      ELSE IF( K.LT.0 .OR. K.GT.MAX( MU, MV ) ) THEN
         INFO = -5
      ELSE IF( ( IRC.EQ.0 .AND. LDU.LT.MAX( 1, MU ) ) .OR.
     $         ( IRC.EQ.1 .AND. LDU.LT.MAX( 1, N ) ) ) THEN
         INFO = -7
      ELSE IF( ( IRC.EQ.0 .AND. LDV.LT.MAX( 1, MV ) ) .OR.
     $         ( IRC.EQ.1 .AND. LDV.LT.MAX( 1, N ) ) ) THEN
         INFO = -9
      END IF
      IF( INFO.NE.0 ) THEN
         CALL XERBLA( 'ZUNT03', -INFO )
         RETURN
      END IF
*
*     Initialize result
*
      RESULT = ZERO
      IF( MU.EQ.0 .OR. MV.EQ.0 .OR. N.EQ.0 )
     $   RETURN
*
*     Machine constants
*
      ULP = DLAMCH( 'Precision' )
*
      IF( IRC.EQ.0 ) THEN
*
*        Compare rows
*
         RES1 = ZERO
         DO 20 I = 1, K
            LMX = IZAMAX( N, U( I, 1 ), LDU )
            IF( V( I, LMX ).EQ.DCMPLX( ZERO ) ) THEN
               SV = ONE
            ELSE
               SV = ABS( V( I, LMX ) ) / V( I, LMX )
            END IF
            IF( U( I, LMX ).EQ.DCMPLX( ZERO ) ) THEN
               SU = ONE
            ELSE
               SU = ABS( U( I, LMX ) ) / U( I, LMX )
            END IF
            S = SV / SU
            DO 10 J = 1, N
               RES1 = MAX( RES1, ABS( U( I, J )-S*V( I, J ) ) )
   10       CONTINUE
   20    CONTINUE
         RES1 = RES1 / ( DBLE( N )*ULP )
*
*        Compute orthogonality of rows of V.
*
         CALL ZUNT01( 'Rows', MV, N, V, LDV, WORK, LWORK, RWORK, RES2 )
*
      ELSE
*
*        Compare columns
*
         RES1 = ZERO
         DO 40 I = 1, K
            LMX = IZAMAX( N, U( 1, I ), 1 )
            IF( V( LMX, I ).EQ.DCMPLX( ZERO ) ) THEN
               SV = ONE
            ELSE
               SV = ABS( V( LMX, I ) ) / V( LMX, I )
            END IF
            IF( U( LMX, I ).EQ.DCMPLX( ZERO ) ) THEN
               SU = ONE
            ELSE
               SU = ABS( U( LMX, I ) ) / U( LMX, I )
            END IF
            S = SV / SU
            DO 30 J = 1, N
               RES1 = MAX( RES1, ABS( U( J, I )-S*V( J, I ) ) )
   30       CONTINUE
   40    CONTINUE
         RES1 = RES1 / ( DBLE( N )*ULP )
*
*        Compute orthogonality of columns of V.
*
         CALL ZUNT01( 'Columns', N, MV, V, LDV, WORK, LWORK, RWORK,
     $                RES2 )
      END IF
*
      RESULT = MIN( MAX( RES1, RES2 ), ONE / ULP )
      RETURN
*
*     End of ZUNT03
*
      END