LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sglmts.f
Go to the documentation of this file.
1 *> \brief \b SGLMTS
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 SGLMTS( N, M, P, A, AF, LDA, B, BF, LDB, D, DF,
12 * X, U, WORK, LWORK, RWORK, RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER LDA, LDB, LWORK, M, P, N
16 * REAL RESULT
17 * ..
18 * .. Array Arguments ..
19 * REAL A( LDA, * ), AF( LDA, * ), B( LDB, * ),
20 * $ BF( LDB, * ), RWORK( * ), D( * ), DF( * ),
21 * $ U( * ), WORK( LWORK ), X( * )
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> SGLMTS tests SGGGLM - a subroutine for solving the generalized
30 *> linear model problem.
31 *> \endverbatim
32 *
33 * Arguments:
34 * ==========
35 *
36 *> \param[in] N
37 *> \verbatim
38 *> N is INTEGER
39 *> The number of rows of the matrices A and B. N >= 0.
40 *> \endverbatim
41 *>
42 *> \param[in] M
43 *> \verbatim
44 *> M is INTEGER
45 *> The number of columns of the matrix A. M >= 0.
46 *> \endverbatim
47 *>
48 *> \param[in] P
49 *> \verbatim
50 *> P is INTEGER
51 *> The number of columns of the matrix B. P >= 0.
52 *> \endverbatim
53 *>
54 *> \param[in] A
55 *> \verbatim
56 *> A is REAL array, dimension (LDA,M)
57 *> The N-by-M matrix A.
58 *> \endverbatim
59 *>
60 *> \param[out] AF
61 *> \verbatim
62 *> AF is REAL array, dimension (LDA,M)
63 *> \endverbatim
64 *>
65 *> \param[in] LDA
66 *> \verbatim
67 *> LDA is INTEGER
68 *> The leading dimension of the arrays A, AF. LDA >= max(M,N).
69 *> \endverbatim
70 *>
71 *> \param[in] B
72 *> \verbatim
73 *> B is REAL array, dimension (LDB,P)
74 *> The N-by-P matrix A.
75 *> \endverbatim
76 *>
77 *> \param[out] BF
78 *> \verbatim
79 *> BF is REAL array, dimension (LDB,P)
80 *> \endverbatim
81 *>
82 *> \param[in] LDB
83 *> \verbatim
84 *> LDB is INTEGER
85 *> The leading dimension of the arrays B, BF. LDB >= max(P,N).
86 *> \endverbatim
87 *>
88 *> \param[in] D
89 *> \verbatim
90 *> D is REAL array, dimension( N )
91 *> On input, the left hand side of the GLM.
92 *> \endverbatim
93 *>
94 *> \param[out] DF
95 *> \verbatim
96 *> DF is REAL array, dimension( N )
97 *> \endverbatim
98 *>
99 *> \param[out] X
100 *> \verbatim
101 *> X is REAL array, dimension( M )
102 *> solution vector X in the GLM problem.
103 *> \endverbatim
104 *>
105 *> \param[out] U
106 *> \verbatim
107 *> U is REAL array, dimension( P )
108 *> solution vector U in the GLM problem.
109 *> \endverbatim
110 *>
111 *> \param[out] WORK
112 *> \verbatim
113 *> WORK is REAL array, dimension (LWORK)
114 *> \endverbatim
115 *>
116 *> \param[in] LWORK
117 *> \verbatim
118 *> LWORK is INTEGER
119 *> The dimension of the array WORK.
120 *> \endverbatim
121 *>
122 *> \param[out] RWORK
123 *> \verbatim
124 *> RWORK is REAL array, dimension (M)
125 *> \endverbatim
126 *>
127 *> \param[out] RESULT
128 *> \verbatim
129 *> RESULT is REAL
130 *> The test ratio:
131 *> norm( d - A*x - B*u )
132 *> RESULT = -----------------------------------------
133 *> (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
134 *> \endverbatim
135 *
136 * Authors:
137 * ========
138 *
139 *> \author Univ. of Tennessee
140 *> \author Univ. of California Berkeley
141 *> \author Univ. of Colorado Denver
142 *> \author NAG Ltd.
143 *
144 *> \date November 2011
145 *
146 *> \ingroup single_eig
147 *
148 * =====================================================================
149  SUBROUTINE sglmts( N, M, P, A, AF, LDA, B, BF, LDB, D, DF,
150  $ x, u, work, lwork, rwork, result )
151 *
152 * -- LAPACK test routine (version 3.4.0) --
153 * -- LAPACK is a software package provided by Univ. of Tennessee, --
154 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155 * November 2011
156 *
157 * .. Scalar Arguments ..
158  INTEGER LDA, LDB, LWORK, M, P, N
159  REAL RESULT
160 * ..
161 * .. Array Arguments ..
162  REAL A( lda, * ), AF( lda, * ), B( ldb, * ),
163  $ bf( ldb, * ), rwork( * ), d( * ), df( * ),
164  $ u( * ), work( lwork ), x( * )
165 *
166 * ====================================================================
167 *
168 * .. Parameters ..
169  REAL ZERO, ONE
170  parameter ( zero = 0.0e+0, one = 1.0e+0 )
171 * ..
172 * .. Local Scalars ..
173  INTEGER INFO
174  REAL ANORM, BNORM, EPS, XNORM, YNORM, DNORM, UNFL
175 * ..
176 * .. External Functions ..
177  REAL SASUM, SLAMCH, SLANGE
178  EXTERNAL sasum, slamch, slange
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL slacpy
182 *
183 * .. Intrinsic Functions ..
184  INTRINSIC max
185 * ..
186 * .. Executable Statements ..
187 *
188  eps = slamch( 'Epsilon' )
189  unfl = slamch( 'Safe minimum' )
190  anorm = max( slange( '1', n, m, a, lda, rwork ), unfl )
191  bnorm = max( slange( '1', n, p, b, ldb, rwork ), unfl )
192 *
193 * Copy the matrices A and B to the arrays AF and BF,
194 * and the vector D the array DF.
195 *
196  CALL slacpy( 'Full', n, m, a, lda, af, lda )
197  CALL slacpy( 'Full', n, p, b, ldb, bf, ldb )
198  CALL scopy( n, d, 1, df, 1 )
199 *
200 * Solve GLM problem
201 *
202  CALL sggglm( n, m, p, af, lda, bf, ldb, df, x, u, work, lwork,
203  $ info )
204 *
205 * Test the residual for the solution of LSE
206 *
207 * norm( d - A*x - B*u )
208 * RESULT = -----------------------------------------
209 * (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
210 *
211  CALL scopy( n, d, 1, df, 1 )
212  CALL sgemv( 'No transpose', n, m, -one, a, lda, x, 1,
213  $ one, df, 1 )
214 *
215  CALL sgemv( 'No transpose', n, p, -one, b, ldb, u, 1,
216  $ one, df, 1 )
217 *
218  dnorm = sasum( n, df, 1 )
219  xnorm = sasum( m, x, 1 ) + sasum( p, u, 1 )
220  ynorm = anorm + bnorm
221 *
222  IF( xnorm.LE.zero ) THEN
223  result = zero
224  ELSE
225  result = ( ( dnorm / ynorm ) / xnorm ) /eps
226  END IF
227 *
228  RETURN
229 *
230 * End of SGLMTS
231 *
232  END
subroutine sggglm(N, M, P, A, LDA, B, LDB, D, X, Y, WORK, LWORK, INFO)
SGGGLM
Definition: sggglm.f:187
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
subroutine slacpy(UPLO, M, N, A, LDA, B, LDB)
SLACPY copies all or part of one two-dimensional array to another.
Definition: slacpy.f:105
subroutine sglmts(N, M, P, A, AF, LDA, B, BF, LDB, D, DF, X, U, WORK, LWORK, RWORK, RESULT)
SGLMTS
Definition: sglmts.f:151
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53