OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cqrt04.f
Go to the documentation of this file.
1*> \brief \b CQRT04
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE CQRT04(M,N,NB,RESULT)
12*
13* .. Scalar Arguments ..
14* INTEGER M, N, NB, LDT
15* .. Return values ..
16* REAL RESULT(6)
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> CQRT04 tests CGEQRT and CGEMQRT.
25*> \endverbatim
26*
27* Arguments:
28* ==========
29*
30*> \param[in] M
31*> \verbatim
32*> M is INTEGER
33*> Number of rows in test matrix.
34*> \endverbatim
35*>
36*> \param[in] N
37*> \verbatim
38*> N is INTEGER
39*> Number of columns in test matrix.
40*> \endverbatim
41*>
42*> \param[in] NB
43*> \verbatim
44*> NB is INTEGER
45*> Block size of test matrix. NB <= Min(M,N).
46*> \endverbatim
47*>
48*> \param[out] RESULT
49*> \verbatim
50*> RESULT is REAL array, dimension (6)
51*> Results of each of the six tests below.
52*>
53*> RESULT(1) = | A - Q R |
54*> RESULT(2) = | I - Q^H Q |
55*> RESULT(3) = | Q C - Q C |
56*> RESULT(4) = | Q^H C - Q^H C |
57*> RESULT(5) = | C Q - C Q |
58*> RESULT(6) = | C Q^H - C Q^H |
59*> \endverbatim
60*
61* Authors:
62* ========
63*
64*> \author Univ. of Tennessee
65*> \author Univ. of California Berkeley
66*> \author Univ. of Colorado Denver
67*> \author NAG Ltd.
68*
69*> \ingroup complex_lin
70*
71* =====================================================================
72 SUBROUTINE cqrt04(M,N,NB,RESULT)
73 IMPLICIT NONE
74*
75* -- LAPACK test routine --
76* -- LAPACK is a software package provided by Univ. of Tennessee, --
77* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
78*
79* .. Scalar Arguments ..
80 INTEGER M, N, NB, LDT
81* .. Return values ..
82 REAL RESULT(6)
83*
84* =====================================================================
85*
86* ..
87* .. Local allocatable arrays
88 COMPLEX, ALLOCATABLE :: AF(:,:), Q(:,:),
89 $ R(:,:), WORK( : ), T(:,:),
90 $ CF(:,:), DF(:,:), A(:,:), C(:,:), D(:,:)
91 REAL, ALLOCATABLE :: RWORK(:)
92*
93* .. Parameters ..
94 REAL ZERO
95 COMPLEX ONE, CZERO
96 parameter( zero = 0.0, one = (1.0,0.0), czero=(0.0,0.0) )
97* ..
98* .. Local Scalars ..
99 INTEGER INFO, J, K, L, LWORK
100 REAL ANORM, EPS, RESID, CNORM, DNORM
101* ..
102* .. Local Arrays ..
103 INTEGER ISEED( 4 )
104* ..
105* .. External Functions ..
106 REAL SLAMCH
107 REAL CLANGE, CLANSY
108 LOGICAL LSAME
109 EXTERNAL slamch, clange, clansy, lsame
110* ..
111* .. Intrinsic Functions ..
112 INTRINSIC max, min
113* ..
114* .. Data statements ..
115 DATA iseed / 1988, 1989, 1990, 1991 /
116*
117 eps = slamch( 'Epsilon' )
118 k = min(m,n)
119 l = max(m,n)
120 lwork = max(2,l)*max(2,l)*nb
121*
122* Dynamically allocate local arrays
123*
124 ALLOCATE ( a(m,n), af(m,n), q(m,m), r(m,l), rwork(l),
125 $ work(lwork), t(nb,n), c(m,n), cf(m,n),
126 $ d(n,m), df(n,m) )
127*
128* Put random numbers into A and copy to AF
129*
130 ldt=nb
131 DO j=1,n
132 CALL clarnv( 2, iseed, m, a( 1, j ) )
133 END DO
134 CALL clacpy( 'Full', m, n, a, m, af, m )
135*
136* Factor the matrix A in the array AF.
137*
138 CALL cgeqrt( m, n, nb, af, m, t, ldt, work, info )
139*
140* Generate the m-by-m matrix Q
141*
142 CALL claset( 'Full', m, m, czero, one, q, m )
143 CALL cgemqrt( 'r', 'n', M, M, K, NB, AF, M, T, LDT, Q, M,
144 $ WORK, INFO )
145*
146* Copy R
147*
148 CALL CLASET( 'full', M, N, CZERO, CZERO, R, M )
149 CALL CLACPY( 'upper', M, N, AF, M, R, M )
150*
151* Compute |R - Q'*A| / |A| and store in RESULT(1)
152*
153 CALL CGEMM( 'c', 'n', M, N, M, -ONE, Q, M, A, M, ONE, R, M )
154 ANORM = CLANGE( '1', M, N, A, M, RWORK )
155 RESID = CLANGE( '1', M, N, R, M, RWORK )
156.GT. IF( ANORMZERO ) THEN
157 RESULT( 1 ) = RESID / (EPS*MAX(1,M)*ANORM)
158 ELSE
159 RESULT( 1 ) = ZERO
160 END IF
161*
162* Compute |I - Q'*Q| and store in RESULT(2)
163*
164 CALL CLASET( 'full', M, M, CZERO, ONE, R, M )
165 CALL CHERK( 'u', 'c', M, M, REAL(-ONE), Q, M, REAL(ONE), R, M )
166 RESID = CLANSY( '1', 'upper', M, R, M, RWORK )
167 RESULT( 2 ) = RESID / (EPS*MAX(1,M))
168*
169* Generate random m-by-n matrix C and a copy CF
170*
171 DO J=1,N
172 CALL CLARNV( 2, ISEED, M, C( 1, J ) )
173 END DO
174 CNORM = CLANGE( '1', M, N, C, M, RWORK)
175 CALL CLACPY( 'full', M, N, C, M, CF, M )
176*
177* Apply Q to C as Q*C
178*
179 CALL CGEMQRT( 'l', 'n', M, N, K, NB, AF, M, T, NB, CF, M,
180 $ WORK, INFO)
181*
182* Compute |Q*C - Q*C| / |C|
183*
184 CALL CGEMM( 'n', 'n', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
185 RESID = CLANGE( '1', M, N, CF, M, RWORK )
186.GT. IF( CNORMZERO ) THEN
187 RESULT( 3 ) = RESID / (EPS*MAX(1,M)*CNORM)
188 ELSE
189 RESULT( 3 ) = ZERO
190 END IF
191*
192* Copy C into CF again
193*
194 CALL CLACPY( 'full', M, N, C, M, CF, M )
195*
196* Apply Q to C as QT*C
197*
198 CALL CGEMQRT( 'l', 'c', M, N, K, NB, AF, M, T, NB, CF, M,
199 $ WORK, INFO)
200*
201* Compute |QT*C - QT*C| / |C|
202*
203 CALL CGEMM( 'c', 'n', M, N, M, -ONE, Q, M, C, M, ONE, CF, M )
204 RESID = CLANGE( '1', M, N, CF, M, RWORK )
205.GT. IF( CNORMZERO ) THEN
206 RESULT( 4 ) = RESID / (EPS*MAX(1,M)*CNORM)
207 ELSE
208 RESULT( 4 ) = ZERO
209 END IF
210*
211* Generate random n-by-m matrix D and a copy DF
212*
213 DO J=1,M
214 CALL CLARNV( 2, ISEED, N, D( 1, J ) )
215 END DO
216 DNORM = CLANGE( '1', N, M, D, N, RWORK)
217 CALL CLACPY( 'full', N, M, D, N, DF, N )
218*
219* Apply Q to D as D*Q
220*
221 CALL CGEMQRT( 'r', 'n', N, M, K, NB, AF, M, T, NB, DF, N,
222 $ WORK, INFO)
223*
224* Compute |D*Q - D*Q| / |D|
225*
226 CALL CGEMM( 'n', 'n', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
227 RESID = CLANGE( '1', N, M, DF, N, RWORK )
228.GT. IF( CNORMZERO ) THEN
229 RESULT( 5 ) = RESID / (EPS*MAX(1,M)*DNORM)
230 ELSE
231 RESULT( 5 ) = ZERO
232 END IF
233*
234* Copy D into DF again
235*
236 CALL CLACPY( 'full', N, M, D, N, DF, N )
237*
238* Apply Q to D as D*QT
239*
240 CALL CGEMQRT( 'r', 'c', N, M, K, NB, AF, M, T, NB, DF, N,
241 $ WORK, INFO)
242*
243* Compute |D*QT - D*QT| / |D|
244*
245 CALL CGEMM( 'n', 'c', N, M, M, -ONE, D, N, Q, M, ONE, DF, N )
246 RESID = CLANGE( '1', N, M, DF, N, RWORK )
247.GT. IF( CNORMZERO ) THEN
248 RESULT( 6 ) = RESID / (EPS*MAX(1,M)*DNORM)
249 ELSE
250 RESULT( 6 ) = ZERO
251 END IF
252*
253* Deallocate all arrays
254*
255 DEALLOCATE ( A, AF, Q, R, RWORK, WORK, T, C, D, CF, DF)
256*
257 RETURN
258 END
259
subroutine cgeqrt(m, n, nb, a, lda, t, ldt, work, info)
CGEQRT
Definition cgeqrt.f:141
subroutine cgemqrt(side, trans, m, n, k, nb, v, ldv, t, ldt, c, ldc, work, info)
CGEMQRT
Definition cgemqrt.f:168
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
Definition clacpy.f:103
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
subroutine clarnv(idist, iseed, n, x)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition clarnv.f:99
subroutine cqrt04(m, n, nb, result)
CQRT04
Definition cqrt04.f:73
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21