LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ sglmts()

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.

Definition at line 147 of file sglmts.f.

149*
150* -- LAPACK test routine --
151* -- LAPACK is a software package provided by Univ. of Tennessee, --
152* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153*
154* .. Scalar Arguments ..
155 INTEGER LDA, LDB, LWORK, M, P, N
156 REAL RESULT
157* ..
158* .. Array Arguments ..
159 REAL A( LDA, * ), AF( LDA, * ), B( LDB, * ),
160 $ BF( LDB, * ), RWORK( * ), D( * ), DF( * ),
161 $ U( * ), WORK( LWORK ), X( * )
162*
163* ====================================================================
164*
165* .. Parameters ..
166 REAL ZERO, ONE
167 parameter( zero = 0.0e+0, one = 1.0e+0 )
168* ..
169* .. Local Scalars ..
170 INTEGER INFO
171 REAL ANORM, BNORM, EPS, XNORM, YNORM, DNORM, UNFL
172* ..
173* .. External Functions ..
174 REAL SASUM, SLAMCH, SLANGE
175 EXTERNAL sasum, slamch, slange
176* ..
177* .. External Subroutines ..
178 EXTERNAL slacpy
179*
180* .. Intrinsic Functions ..
181 INTRINSIC max
182* ..
183* .. Executable Statements ..
184*
185 eps = slamch( 'Epsilon' )
186 unfl = slamch( 'Safe minimum' )
187 anorm = max( slange( '1', n, m, a, lda, rwork ), unfl )
188 bnorm = max( slange( '1', n, p, b, ldb, rwork ), unfl )
189*
190* Copy the matrices A and B to the arrays AF and BF,
191* and the vector D the array DF.
192*
193 CALL slacpy( 'Full', n, m, a, lda, af, lda )
194 CALL slacpy( 'Full', n, p, b, ldb, bf, ldb )
195 CALL scopy( n, d, 1, df, 1 )
196*
197* Solve GLM problem
198*
199 CALL sggglm( n, m, p, af, lda, bf, ldb, df, x, u, work, lwork,
200 $ info )
201*
202* Test the residual for the solution of LSE
203*
204* norm( d - A*x - B*u )
205* RESULT = -----------------------------------------
206* (norm(A)+norm(B))*(norm(x)+norm(u))*EPS
207*
208 CALL scopy( n, d, 1, df, 1 )
209 CALL sgemv( 'No transpose', n, m, -one, a, lda, x, 1,
210 $ one, df, 1 )
211*
212 CALL sgemv( 'No transpose', n, p, -one, b, ldb, u, 1,
213 $ one, df, 1 )
214*
215 dnorm = sasum( n, df, 1 )
216 xnorm = sasum( m, x, 1 ) + sasum( p, u, 1 )
217 ynorm = anorm + bnorm
218*
219 IF( xnorm.LE.zero ) THEN
220 result = zero
221 ELSE
222 result = ( ( dnorm / ynorm ) / xnorm ) /eps
223 END IF
224*
225 RETURN
226*
227* End of SGLMTS
228*
real function sasum(n, sx, incx)
SASUM
Definition sasum.f:72
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
Definition scopy.f:82
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine sggglm(n, m, p, a, lda, b, ldb, d, x, y, work, lwork, info)
SGGGLM
Definition sggglm.f:194
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
Definition slacpy.f:101
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
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:112
Here is the call graph for this function:
Here is the caller graph for this function: