LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sglmts ( integer  N,
integer  M,
integer  P,
real, dimension( lda, * )  A,
real, dimension( lda, * )  AF,
integer  LDA,
real, dimension( ldb, * )  B,
real, dimension( ldb, * )  BF,
integer  LDB,
real, dimension( * )  D,
real, dimension( * )  DF,
real, dimension( * )  X,
real, dimension( * )  U,
real, dimension( lwork )  WORK,
integer  LWORK,
real, dimension( * )  RWORK,
real  RESULT 
)

SGLMTS

Purpose:
 SGLMTS tests SGGGLM - a subroutine for solving the generalized
 linear model problem.
Parameters
[in]N
          N is INTEGER
          The number of rows of the matrices A and B.  N >= 0.
[in]M
          M is INTEGER
          The number of columns of the matrix A.  M >= 0.
[in]P
          P is INTEGER
          The number of columns of the matrix B.  P >= 0.
[in]A
          A is REAL array, dimension (LDA,M)
          The N-by-M matrix A.
[out]AF
          AF is REAL array, dimension (LDA,M)
[in]LDA
          LDA is INTEGER
          The leading dimension of the arrays A, AF. LDA >= max(M,N).
[in]B
          B is REAL array, dimension (LDB,P)
          The N-by-P matrix A.
[out]BF
          BF is REAL array, dimension (LDB,P)
[in]LDB
          LDB is INTEGER
          The leading dimension of the arrays B, BF. LDB >= max(P,N).
[in]D
          D is REAL array, dimension( N )
          On input, the left hand side of the GLM.
[out]DF
          DF is REAL array, dimension( N )
[out]X
          X is REAL array, dimension( M )
          solution vector X in the GLM problem.
[out]U
          U is REAL array, dimension( P )
          solution vector U in the GLM problem.
[out]WORK
          WORK is REAL array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK.
[out]RWORK
          RWORK is REAL array, dimension (M)
[out]RESULT
          RESULT is REAL
          The test ratio:
                           norm( d - A*x - B*u )
            RESULT = -----------------------------------------
                     (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 151 of file sglmts.f.

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 *
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
real function slange(NORM, M, N, A, LDA, WORK)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: slange.f:116
real function sasum(N, SX, INCX)
SASUM
Definition: sasum.f:54
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:53

Here is the call graph for this function:

Here is the caller graph for this function: