LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dqrt14.f
Go to the documentation of this file.
1 *> \brief \b DQRT14
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * DOUBLE PRECISION FUNCTION DQRT14( TRANS, M, N, NRHS, A, LDA, X,
12 * LDX, WORK, LWORK )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER TRANS
16 * INTEGER LDA, LDX, LWORK, M, N, NRHS
17 * ..
18 * .. Array Arguments ..
19 * DOUBLE PRECISION A( LDA, * ), WORK( LWORK ), X( LDX, * )
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> DQRT14 checks whether X is in the row space of A or A'. It does so
29 *> by scaling both X and A such that their norms are in the range
30 *> [sqrt(eps), 1/sqrt(eps)], then computing a QR factorization of [A,X]
31 *> (if TRANS = 'T') or an LQ factorization of [A',X]' (if TRANS = 'N'),
32 *> and returning the norm of the trailing triangle, scaled by
33 *> MAX(M,N,NRHS)*eps.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] TRANS
40 *> \verbatim
41 *> TRANS is CHARACTER*1
42 *> = 'N': No transpose, check for X in the row space of A
43 *> = 'T': Transpose, check for X in the row space of A'.
44 *> \endverbatim
45 *>
46 *> \param[in] M
47 *> \verbatim
48 *> M is INTEGER
49 *> The number of rows of the matrix A.
50 *> \endverbatim
51 *>
52 *> \param[in] N
53 *> \verbatim
54 *> N is INTEGER
55 *> The number of columns of the matrix A.
56 *> \endverbatim
57 *>
58 *> \param[in] NRHS
59 *> \verbatim
60 *> NRHS is INTEGER
61 *> The number of right hand sides, i.e., the number of columns
62 *> of X.
63 *> \endverbatim
64 *>
65 *> \param[in] A
66 *> \verbatim
67 *> A is DOUBLE PRECISION array, dimension (LDA,N)
68 *> The M-by-N matrix A.
69 *> \endverbatim
70 *>
71 *> \param[in] LDA
72 *> \verbatim
73 *> LDA is INTEGER
74 *> The leading dimension of the array A.
75 *> \endverbatim
76 *>
77 *> \param[in] X
78 *> \verbatim
79 *> X is DOUBLE PRECISION array, dimension (LDX,NRHS)
80 *> If TRANS = 'N', the N-by-NRHS matrix X.
81 *> IF TRANS = 'T', the M-by-NRHS matrix X.
82 *> \endverbatim
83 *>
84 *> \param[in] LDX
85 *> \verbatim
86 *> LDX is INTEGER
87 *> The leading dimension of the array X.
88 *> \endverbatim
89 *>
90 *> \param[out] WORK
91 *> \verbatim
92 *> WORK is DOUBLE PRECISION array dimension (LWORK)
93 *> \endverbatim
94 *>
95 *> \param[in] LWORK
96 *> \verbatim
97 *> LWORK is INTEGER
98 *> length of workspace array required
99 *> If TRANS = 'N', LWORK >= (M+NRHS)*(N+2);
100 *> if TRANS = 'T', LWORK >= (N+NRHS)*(M+2).
101 *> \endverbatim
102 *
103 * Authors:
104 * ========
105 *
106 *> \author Univ. of Tennessee
107 *> \author Univ. of California Berkeley
108 *> \author Univ. of Colorado Denver
109 *> \author NAG Ltd.
110 *
111 *> \date November 2011
112 *
113 *> \ingroup double_lin
114 *
115 * =====================================================================
116  DOUBLE PRECISION FUNCTION dqrt14( TRANS, M, N, NRHS, A, LDA, X,
117  $ ldx, work, lwork )
118 *
119 * -- LAPACK test routine (version 3.4.0) --
120 * -- LAPACK is a software package provided by Univ. of Tennessee, --
121 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122 * November 2011
123 *
124 * .. Scalar Arguments ..
125  CHARACTER TRANS
126  INTEGER LDA, LDX, LWORK, M, N, NRHS
127 * ..
128 * .. Array Arguments ..
129  DOUBLE PRECISION A( lda, * ), WORK( lwork ), X( ldx, * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  DOUBLE PRECISION ZERO, ONE
136  parameter ( zero = 0.0d0, one = 1.0d0 )
137 * ..
138 * .. Local Scalars ..
139  LOGICAL TPSD
140  INTEGER I, INFO, J, LDWORK
141  DOUBLE PRECISION ANRM, ERR, XNRM
142 * ..
143 * .. Local Arrays ..
144  DOUBLE PRECISION RWORK( 1 )
145 * ..
146 * .. External Functions ..
147  LOGICAL LSAME
148  DOUBLE PRECISION DLAMCH, DLANGE
149  EXTERNAL lsame, dlamch, dlange
150 * ..
151 * .. External Subroutines ..
152  EXTERNAL dgelq2, dgeqr2, dlacpy, dlascl, xerbla
153 * ..
154 * .. Intrinsic Functions ..
155  INTRINSIC abs, dble, max, min
156 * ..
157 * .. Executable Statements ..
158 *
159  dqrt14 = zero
160  IF( lsame( trans, 'N' ) ) THEN
161  ldwork = m + nrhs
162  tpsd = .false.
163  IF( lwork.LT.( m+nrhs )*( n+2 ) ) THEN
164  CALL xerbla( 'DQRT14', 10 )
165  RETURN
166  ELSE IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
167  RETURN
168  END IF
169  ELSE IF( lsame( trans, 'T' ) ) THEN
170  ldwork = m
171  tpsd = .true.
172  IF( lwork.LT.( n+nrhs )*( m+2 ) ) THEN
173  CALL xerbla( 'DQRT14', 10 )
174  RETURN
175  ELSE IF( m.LE.0 .OR. nrhs.LE.0 ) THEN
176  RETURN
177  END IF
178  ELSE
179  CALL xerbla( 'DQRT14', 1 )
180  RETURN
181  END IF
182 *
183 * Copy and scale A
184 *
185  CALL dlacpy( 'All', m, n, a, lda, work, ldwork )
186  anrm = dlange( 'M', m, n, work, ldwork, rwork )
187  IF( anrm.NE.zero )
188  $ CALL dlascl( 'G', 0, 0, anrm, one, m, n, work, ldwork, info )
189 *
190 * Copy X or X' into the right place and scale it
191 *
192  IF( tpsd ) THEN
193 *
194 * Copy X into columns n+1:n+nrhs of work
195 *
196  CALL dlacpy( 'All', m, nrhs, x, ldx, work( n*ldwork+1 ),
197  $ ldwork )
198  xnrm = dlange( 'M', m, nrhs, work( n*ldwork+1 ), ldwork,
199  $ rwork )
200  IF( xnrm.NE.zero )
201  $ CALL dlascl( 'G', 0, 0, xnrm, one, m, nrhs,
202  $ work( n*ldwork+1 ), ldwork, info )
203  anrm = dlange( 'One-norm', m, n+nrhs, work, ldwork, rwork )
204 *
205 * Compute QR factorization of X
206 *
207  CALL dgeqr2( m, n+nrhs, work, ldwork,
208  $ work( ldwork*( n+nrhs )+1 ),
209  $ work( ldwork*( n+nrhs )+min( m, n+nrhs )+1 ),
210  $ info )
211 *
212 * Compute largest entry in upper triangle of
213 * work(n+1:m,n+1:n+nrhs)
214 *
215  err = zero
216  DO 20 j = n + 1, n + nrhs
217  DO 10 i = n + 1, min( m, j )
218  err = max( err, abs( work( i+( j-1 )*m ) ) )
219  10 CONTINUE
220  20 CONTINUE
221 *
222  ELSE
223 *
224 * Copy X' into rows m+1:m+nrhs of work
225 *
226  DO 40 i = 1, n
227  DO 30 j = 1, nrhs
228  work( m+j+( i-1 )*ldwork ) = x( i, j )
229  30 CONTINUE
230  40 CONTINUE
231 *
232  xnrm = dlange( 'M', nrhs, n, work( m+1 ), ldwork, rwork )
233  IF( xnrm.NE.zero )
234  $ CALL dlascl( 'G', 0, 0, xnrm, one, nrhs, n, work( m+1 ),
235  $ ldwork, info )
236 *
237 * Compute LQ factorization of work
238 *
239  CALL dgelq2( ldwork, n, work, ldwork, work( ldwork*n+1 ),
240  $ work( ldwork*( n+1 )+1 ), info )
241 *
242 * Compute largest entry in lower triangle in
243 * work(m+1:m+nrhs,m+1:n)
244 *
245  err = zero
246  DO 60 j = m + 1, n
247  DO 50 i = j, ldwork
248  err = max( err, abs( work( i+( j-1 )*ldwork ) ) )
249  50 CONTINUE
250  60 CONTINUE
251 *
252  END IF
253 *
254  dqrt14 = err / ( dble( max( m, n, nrhs ) )*dlamch( 'Epsilon' ) )
255 *
256  RETURN
257 *
258 * End of DQRT14
259 *
260  END
subroutine dgeqr2(M, N, A, LDA, TAU, WORK, INFO)
DGEQR2 computes the QR factorization of a general rectangular matrix using an unblocked algorithm...
Definition: dgeqr2.f:123
subroutine dlacpy(UPLO, M, N, A, LDA, B, LDB)
DLACPY copies all or part of one two-dimensional array to another.
Definition: dlacpy.f:105
subroutine dlascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
DLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition: dlascl.f:145
subroutine dgelq2(M, N, A, LDA, TAU, WORK, INFO)
DGELQ2 computes the LQ factorization of a general rectangular matrix using an unblocked algorithm...
Definition: dgelq2.f:123
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
double precision function dqrt14(TRANS, M, N, NRHS, A, LDA, X, LDX, WORK, LWORK)
DQRT14
Definition: dqrt14.f:118