LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sqrt15 ( integer  SCALE,
integer  RKSEL,
integer  M,
integer  N,
integer  NRHS,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( ldb, * )  B,
integer  LDB,
real, dimension( * )  S,
integer  RANK,
real  NORMA,
real  NORMB,
integer, dimension( 4 )  ISEED,
real, dimension( lwork )  WORK,
integer  LWORK 
)

SQRT15

Purpose:
 SQRT15 generates a matrix with full or deficient rank and of various
 norms.
Parameters
[in]SCALE
          SCALE is INTEGER
          SCALE = 1: normally scaled matrix
          SCALE = 2: matrix scaled up
          SCALE = 3: matrix scaled down
[in]RKSEL
          RKSEL is INTEGER
          RKSEL = 1: full rank matrix
          RKSEL = 2: rank-deficient matrix
[in]M
          M is INTEGER
          The number of rows of the matrix A.
[in]N
          N is INTEGER
          The number of columns of A.
[in]NRHS
          NRHS is INTEGER
          The number of columns of B.
[out]A
          A is REAL array, dimension (LDA,N)
          The M-by-N matrix A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
[out]B
          B is REAL array, dimension (LDB, NRHS)
          A matrix that is in the range space of matrix A.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.
[out]S
          S is REAL array, dimension MIN(M,N)
          Singular values of A.
[out]RANK
          RANK is INTEGER
          number of nonzero singular values of A.
[out]NORMA
          NORMA is REAL
          one-norm of A.
[out]NORMB
          NORMB is REAL
          one-norm of B.
[in,out]ISEED
          ISEED is integer array, dimension (4)
          seed for random number generator.
[out]WORK
          WORK is REAL array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          length of work space required.
          LWORK >= MAX(M+MIN(M,N),NRHS*MIN(M,N),2*N+M)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 150 of file sqrt15.f.

150 *
151 * -- LAPACK test routine (version 3.4.0) --
152 * -- LAPACK is a software package provided by Univ. of Tennessee, --
153 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154 * November 2011
155 *
156 * .. Scalar Arguments ..
157  INTEGER lda, ldb, lwork, m, n, nrhs, rank, rksel, scale
158  REAL norma, normb
159 * ..
160 * .. Array Arguments ..
161  INTEGER iseed( 4 )
162  REAL a( lda, * ), b( ldb, * ), s( * ), work( lwork )
163 * ..
164 *
165 * =====================================================================
166 *
167 * .. Parameters ..
168  REAL zero, one, two, svmin
169  parameter ( zero = 0.0e0, one = 1.0e0, two = 2.0e0,
170  $ svmin = 0.1e0 )
171 * ..
172 * .. Local Scalars ..
173  INTEGER info, j, mn
174  REAL bignum, eps, smlnum, temp
175 * ..
176 * .. Local Arrays ..
177  REAL dummy( 1 )
178 * ..
179 * .. External Functions ..
180  REAL sasum, slamch, slange, slarnd, snrm2
181  EXTERNAL sasum, slamch, slange, slarnd, snrm2
182 * ..
183 * .. External Subroutines ..
184  EXTERNAL sgemm, slaord, slarf, slarnv, slaror, slascl,
185  $ slaset, sscal, xerbla
186 * ..
187 * .. Intrinsic Functions ..
188  INTRINSIC abs, max, min
189 * ..
190 * .. Executable Statements ..
191 *
192  mn = min( m, n )
193  IF( lwork.LT.max( m+mn, mn*nrhs, 2*n+m ) ) THEN
194  CALL xerbla( 'SQRT15', 16 )
195  RETURN
196  END IF
197 *
198  smlnum = slamch( 'Safe minimum' )
199  bignum = one / smlnum
200  eps = slamch( 'Epsilon' )
201  smlnum = ( smlnum / eps ) / eps
202  bignum = one / smlnum
203 *
204 * Determine rank and (unscaled) singular values
205 *
206  IF( rksel.EQ.1 ) THEN
207  rank = mn
208  ELSE IF( rksel.EQ.2 ) THEN
209  rank = ( 3*mn ) / 4
210  DO 10 j = rank + 1, mn
211  s( j ) = zero
212  10 CONTINUE
213  ELSE
214  CALL xerbla( 'SQRT15', 2 )
215  END IF
216 *
217  IF( rank.GT.0 ) THEN
218 *
219 * Nontrivial case
220 *
221  s( 1 ) = one
222  DO 30 j = 2, rank
223  20 CONTINUE
224  temp = slarnd( 1, iseed )
225  IF( temp.GT.svmin ) THEN
226  s( j ) = abs( temp )
227  ELSE
228  GO TO 20
229  END IF
230  30 CONTINUE
231  CALL slaord( 'Decreasing', rank, s, 1 )
232 *
233 * Generate 'rank' columns of a random orthogonal matrix in A
234 *
235  CALL slarnv( 2, iseed, m, work )
236  CALL sscal( m, one / snrm2( m, work, 1 ), work, 1 )
237  CALL slaset( 'Full', m, rank, zero, one, a, lda )
238  CALL slarf( 'Left', m, rank, work, 1, two, a, lda,
239  $ work( m+1 ) )
240 *
241 * workspace used: m+mn
242 *
243 * Generate consistent rhs in the range space of A
244 *
245  CALL slarnv( 2, iseed, rank*nrhs, work )
246  CALL sgemm( 'No transpose', 'No transpose', m, nrhs, rank, one,
247  $ a, lda, work, rank, zero, b, ldb )
248 *
249 * work space used: <= mn *nrhs
250 *
251 * generate (unscaled) matrix A
252 *
253  DO 40 j = 1, rank
254  CALL sscal( m, s( j ), a( 1, j ), 1 )
255  40 CONTINUE
256  IF( rank.LT.n )
257  $ CALL slaset( 'Full', m, n-rank, zero, zero, a( 1, rank+1 ),
258  $ lda )
259  CALL slaror( 'Right', 'No initialization', m, n, a, lda, iseed,
260  $ work, info )
261 *
262  ELSE
263 *
264 * work space used 2*n+m
265 *
266 * Generate null matrix and rhs
267 *
268  DO 50 j = 1, mn
269  s( j ) = zero
270  50 CONTINUE
271  CALL slaset( 'Full', m, n, zero, zero, a, lda )
272  CALL slaset( 'Full', m, nrhs, zero, zero, b, ldb )
273 *
274  END IF
275 *
276 * Scale the matrix
277 *
278  IF( scale.NE.1 ) THEN
279  norma = slange( 'Max', m, n, a, lda, dummy )
280  IF( norma.NE.zero ) THEN
281  IF( scale.EQ.2 ) THEN
282 *
283 * matrix scaled up
284 *
285  CALL slascl( 'General', 0, 0, norma, bignum, m, n, a,
286  $ lda, info )
287  CALL slascl( 'General', 0, 0, norma, bignum, mn, 1, s,
288  $ mn, info )
289  CALL slascl( 'General', 0, 0, norma, bignum, m, nrhs, b,
290  $ ldb, info )
291  ELSE IF( scale.EQ.3 ) THEN
292 *
293 * matrix scaled down
294 *
295  CALL slascl( 'General', 0, 0, norma, smlnum, m, n, a,
296  $ lda, info )
297  CALL slascl( 'General', 0, 0, norma, smlnum, mn, 1, s,
298  $ mn, info )
299  CALL slascl( 'General', 0, 0, norma, smlnum, m, nrhs, b,
300  $ ldb, info )
301  ELSE
302  CALL xerbla( 'SQRT15', 1 )
303  RETURN
304  END IF
305  END IF
306  END IF
307 *
308  norma = sasum( mn, s, 1 )
309  normb = slange( 'One-norm', m, nrhs, b, ldb, dummy )
310 *
311  RETURN
312 *
313 * End of SQRT15
314 *
subroutine slascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
SLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition: slascl.f:145
subroutine slarnv(IDIST, ISEED, N, X)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: slarnv.f:99
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine slaror(SIDE, INIT, M, N, A, LDA, ISEED, X, INFO)
SLAROR
Definition: slaror.f:148
subroutine slaset(UPLO, M, N, ALPHA, BETA, A, LDA)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: slaset.f:112
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 snrm2(N, X, INCX)
SNRM2
Definition: snrm2.f:56
real function slarnd(IDIST, ISEED)
SLARND
Definition: slarnd.f:75
real function sasum(N, SX, INCX)
SASUM
Definition: sasum.f:54
subroutine slarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
SLARF applies an elementary reflector to a general rectangular matrix.
Definition: slarf.f:126
subroutine slaord(JOB, N, X, INCX)
SLAORD
Definition: slaord.f:75
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the call graph for this function:

Here is the caller graph for this function: