LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cqrt05 ( integer  M,
integer  N,
integer  L,
integer  NB,
real, dimension(6)  RESULT 
)

CQRT05

Purpose:
 CQRT05 tests CTPQRT and CTPMQRT.
Parameters
[in]M
          M is INTEGER
          Number of rows in lower part of the test matrix.
[in]N
          N is INTEGER
          Number of columns in test matrix.
[in]L
          L is INTEGER
          The number of rows of the upper trapezoidal part the
          lower test matrix.  0 <= L <= M.
[in]NB
          NB is INTEGER
          Block size of test matrix.  NB <= N.
[out]RESULT
          RESULT is REAL array, dimension (6)
          Results of each of the six tests below.

          RESULT(1) = | A - Q R |
          RESULT(2) = | I - Q^H Q |
          RESULT(3) = | Q C - Q C |
          RESULT(4) = | Q^H C - Q^H C |
          RESULT(5) = | C Q - C Q | 
          RESULT(6) = | C Q^H - C Q^H |
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
April 2012

Definition at line 82 of file cqrt05.f.

82  IMPLICIT NONE
83 *
84 * -- LAPACK test routine (version 3.6.1) --
85 * -- LAPACK is a software package provided by Univ. of Tennessee, --
86 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
87 * April 2012
88 *
89 * .. Scalar Arguments ..
90  INTEGER lwork, m, n, l, nb, ldt
91 * .. Return values ..
92  REAL result(6)
93 *
94 * =====================================================================
95 *
96 * ..
97 * .. Local allocatable arrays
98  COMPLEX, ALLOCATABLE :: af(:,:), q(:,:),
99  $ r(:,:), work( : ), t(:,:),
100  $ cf(:,:), df(:,:), a(:,:), c(:,:), d(:,:)
101  REAL, ALLOCATABLE :: rwork(:)
102 *
103 * .. Parameters ..
104  REAL zero
105  COMPLEX one, czero
106  parameter( zero = 0.0, one = (1.0,0.0), czero=(0.0,0.0) )
107 * ..
108 * .. Local Scalars ..
109  INTEGER info, j, k, m2, np1
110  REAL anorm, eps, resid, cnorm, dnorm
111 * ..
112 * .. Local Arrays ..
113  INTEGER iseed( 4 )
114 * ..
115 * .. External Functions ..
116  REAL slamch
117  REAL clange, clansy
118  LOGICAL lsame
119  EXTERNAL slamch, clange, clansy, lsame
120 * ..
121 * .. Data statements ..
122  DATA iseed / 1988, 1989, 1990, 1991 /
123 *
124  eps = slamch( 'Epsilon' )
125  k = n
126  m2 = m+n
127  IF( m.GT.0 ) THEN
128  np1 = n+1
129  ELSE
130  np1 = 1
131  END IF
132  lwork = m2*m2*nb
133 *
134 * Dynamically allocate all arrays
135 *
136  ALLOCATE(a(m2,n),af(m2,n),q(m2,m2),r(m2,m2),rwork(m2),
137  $ work(lwork),t(nb,n),c(m2,n),cf(m2,n),
138  $ d(n,m2),df(n,m2) )
139 *
140 * Put random stuff into A
141 *
142  ldt=nb
143  CALL claset( 'Full', m2, n, czero, czero, a, m2 )
144  CALL claset( 'Full', nb, n, czero, czero, t, nb )
145  DO j=1,n
146  CALL clarnv( 2, iseed, j, a( 1, j ) )
147  END DO
148  IF( m.GT.0 ) THEN
149  DO j=1,n
150  CALL clarnv( 2, iseed, m-l, a( min(n+m,n+1), j ) )
151  END DO
152  END IF
153  IF( l.GT.0 ) THEN
154  DO j=1,n
155  CALL clarnv( 2, iseed, min(j,l), a( min(n+m,n+m-l+1), j ) )
156  END DO
157  END IF
158 *
159 * Copy the matrix A to the array AF.
160 *
161  CALL clacpy( 'Full', m2, n, a, m2, af, m2 )
162 *
163 * Factor the matrix A in the array AF.
164 *
165  CALL ctpqrt( m,n,l,nb,af,m2,af(np1,1),m2,t,ldt,work,info)
166 *
167 * Generate the (M+N)-by-(M+N) matrix Q by applying H to I
168 *
169  CALL claset( 'Full', m2, m2, czero, one, q, m2 )
170  CALL cgemqrt( 'R', 'N', m2, m2, k, nb, af, m2, t, ldt, q, m2,
171  $ work, info )
172 *
173 * Copy R
174 *
175  CALL claset( 'Full', m2, n, czero, czero, r, m2 )
176  CALL clacpy( 'Upper', m2, n, af, m2, r, m2 )
177 *
178 * Compute |R - Q'*A| / |A| and store in RESULT(1)
179 *
180  CALL cgemm( 'C', 'N', m2, n, m2, -one, q, m2, a, m2, one, r, m2 )
181  anorm = clange( '1', m2, n, a, m2, rwork )
182  resid = clange( '1', m2, n, r, m2, rwork )
183  IF( anorm.GT.zero ) THEN
184  result( 1 ) = resid / (eps*anorm*max(1,m2))
185  ELSE
186  result( 1 ) = zero
187  END IF
188 *
189 * Compute |I - Q'*Q| and store in RESULT(2)
190 *
191  CALL claset( 'Full', m2, m2, czero, one, r, m2 )
192  CALL cherk( 'U', 'C', m2, m2, REAL(-ONE), q, m2, REAL(ONE),
193  $ r, m2 )
194  resid = clansy( '1', 'Upper', m2, r, m2, rwork )
195  result( 2 ) = resid / (eps*max(1,m2))
196 *
197 * Generate random m-by-n matrix C and a copy CF
198 *
199  DO j=1,n
200  CALL clarnv( 2, iseed, m2, c( 1, j ) )
201  END DO
202  cnorm = clange( '1', m2, n, c, m2, rwork)
203  CALL clacpy( 'Full', m2, n, c, m2, cf, m2 )
204 *
205 * Apply Q to C as Q*C
206 *
207  CALL ctpmqrt( 'L','N', m,n,k,l,nb,af(np1,1),m2,t,ldt,cf,m2,
208  $ cf(np1,1),m2,work,info)
209 *
210 * Compute |Q*C - Q*C| / |C|
211 *
212  CALL cgemm( 'N', 'N', m2, n, m2, -one, q, m2, c, m2, one, cf, m2 )
213  resid = clange( '1', m2, n, cf, m2, rwork )
214  IF( cnorm.GT.zero ) THEN
215  result( 3 ) = resid / (eps*max(1,m2)*cnorm)
216  ELSE
217  result( 3 ) = zero
218  END IF
219 *
220 * Copy C into CF again
221 *
222  CALL clacpy( 'Full', m2, n, c, m2, cf, m2 )
223 *
224 * Apply Q to C as QT*C
225 *
226  CALL ctpmqrt( 'L','C',m,n,k,l,nb,af(np1,1),m2,t,ldt,cf,m2,
227  $ cf(np1,1),m2,work,info)
228 *
229 * Compute |QT*C - QT*C| / |C|
230 *
231  CALL cgemm('C','N',m2,n,m2,-one,q,m2,c,m2,one,cf,m2)
232  resid = clange( '1', m2, n, cf, m2, rwork )
233  IF( cnorm.GT.zero ) THEN
234  result( 4 ) = resid / (eps*max(1,m2)*cnorm)
235  ELSE
236  result( 4 ) = zero
237  END IF
238 *
239 * Generate random n-by-m matrix D and a copy DF
240 *
241  DO j=1,m2
242  CALL clarnv( 2, iseed, n, d( 1, j ) )
243  END DO
244  dnorm = clange( '1', n, m2, d, n, rwork)
245  CALL clacpy( 'Full', n, m2, d, n, df, n )
246 *
247 * Apply Q to D as D*Q
248 *
249  CALL ctpmqrt('R','N',n,m,n,l,nb,af(np1,1),m2,t,ldt,df,n,
250  $ df(1,np1),n,work,info)
251 *
252 * Compute |D*Q - D*Q| / |D|
253 *
254  CALL cgemm('N','N',n,m2,m2,-one,d,n,q,m2,one,df,n)
255  resid = clange('1',n, m2,df,n,rwork )
256  IF( cnorm.GT.zero ) THEN
257  result( 5 ) = resid / (eps*max(1,m2)*dnorm)
258  ELSE
259  result( 5 ) = zero
260  END IF
261 *
262 * Copy D into DF again
263 *
264  CALL clacpy('Full',n,m2,d,n,df,n )
265 *
266 * Apply Q to D as D*QT
267 *
268  CALL ctpmqrt('R','C',n,m,n,l,nb,af(np1,1),m2,t,ldt,df,n,
269  $ df(1,np1),n,work,info)
270 
271 *
272 * Compute |D*QT - D*QT| / |D|
273 *
274  CALL cgemm( 'N', 'C', n, m2, m2, -one, d, n, q, m2, one, df, n )
275  resid = clange( '1', n, m2, df, n, rwork )
276  IF( cnorm.GT.zero ) THEN
277  result( 6 ) = resid / (eps*max(1,m2)*dnorm)
278  ELSE
279  result( 6 ) = zero
280  END IF
281 *
282 * Deallocate all arrays
283 *
284  DEALLOCATE ( a, af, q, r, rwork, work, t, c, d, cf, df)
285  RETURN
subroutine ctpqrt(M, N, L, NB, A, LDA, B, LDB, T, LDT, WORK, INFO)
CTPQRT
Definition: ctpqrt.f:191
subroutine ctpmqrt(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO)
CTPMQRT
Definition: ctpmqrt.f:218
subroutine cherk(UPLO, TRANS, N, K, ALPHA, A, LDA, BETA, C, LDC)
CHERK
Definition: cherk.f:175
real function clange(NORM, M, N, A, LDA, WORK)
CLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: clange.f:117
subroutine clarnv(IDIST, ISEED, N, X)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: clarnv.f:101
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:108
subroutine cgemqrt(SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT, C, LDC, WORK, INFO)
CGEMQRT
Definition: cgemqrt.f:170
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, or the element of largest absolute value of a complex symmetric matrix.
Definition: clansy.f:125
subroutine clacpy(UPLO, M, N, A, LDA, B, LDB)
CLACPY copies all or part of one two-dimensional array to another.
Definition: clacpy.f:105
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine cgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
CGEMM
Definition: cgemm.f:189
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: