LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sckcsd ( integer  NM,
integer, dimension( * )  MVAL,
integer, dimension( * )  PVAL,
integer, dimension( * )  QVAL,
integer  NMATS,
integer, dimension( 4 )  ISEED,
real  THRESH,
integer  MMAX,
real, dimension( * )  X,
real, dimension( * )  XF,
real, dimension( * )  U1,
real, dimension( * )  U2,
real, dimension( * )  V1T,
real, dimension( * )  V2T,
real, dimension( * )  THETA,
integer, dimension( * )  IWORK,
real, dimension( * )  WORK,
real, dimension( * )  RWORK,
integer  NIN,
integer  NOUT,
integer  INFO 
)

SCKCSD

Purpose:
 SCKCSD tests SORCSD:
        the CSD for an M-by-M orthogonal matrix X partitioned as
        [ X11 X12; X21 X22 ]. X11 is P-by-Q.
Parameters
[in]NM
          NM is INTEGER
          The number of values of M contained in the vector MVAL.
[in]MVAL
          MVAL is INTEGER array, dimension (NM)
          The values of the matrix row dimension M.
[in]PVAL
          PVAL is INTEGER array, dimension (NM)
          The values of the matrix row dimension P.
[in]QVAL
          QVAL is INTEGER array, dimension (NM)
          The values of the matrix column dimension Q.
[in]NMATS
          NMATS is INTEGER
          The number of matrix types to be tested for each combination
          of matrix dimensions.  If NMATS >= NTYPES (the maximum
          number of matrix types), then all the different types are
          generated for testing.  If NMATS < NTYPES, another input line
          is read to get the numbers of the matrix types to be used.
[in,out]ISEED
          ISEED is INTEGER array, dimension (4)
          On entry, the seed of the random number generator.  The array
          elements should be between 0 and 4095, otherwise they will be
          reduced mod 4096, and ISEED(4) must be odd.
          On exit, the next seed in the random number sequence after
          all the test matrices have been generated.
[in]THRESH
          THRESH is REAL
          The threshold value for the test ratios.  A result is
          included in the output file if RESULT >= THRESH.  To have
          every test ratio printed, use THRESH = 0.
[in]MMAX
          MMAX is INTEGER
          The maximum value permitted for M, used in dimensioning the
          work arrays.
[out]X
          X is REAL array, dimension (MMAX*MMAX)
[out]XF
          XF is REAL array, dimension (MMAX*MMAX)
[out]U1
          U1 is REAL array, dimension (MMAX*MMAX)
[out]U2
          U2 is REAL array, dimension (MMAX*MMAX)
[out]V1T
          V1T is REAL array, dimension (MMAX*MMAX)
[out]V2T
          V2T is REAL array, dimension (MMAX*MMAX)
[out]THETA
          THETA is REAL array, dimension (MMAX)
[out]IWORK
          IWORK is INTEGER array, dimension (MMAX)
[out]WORK
          WORK is REAL array
[out]RWORK
          RWORK is REAL array
[in]NIN
          NIN is INTEGER
          The unit number for input.
[in]NOUT
          NOUT is INTEGER
          The unit number for output.
[out]INFO
          INFO is INTEGER
          = 0 :  successful exit
          > 0 :  If SLAROR returns an error code, the absolute value
                 of it is returned.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 186 of file sckcsd.f.

186 *
187 * -- LAPACK test routine (version 3.4.0) --
188 * -- LAPACK is a software package provided by Univ. of Tennessee, --
189 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
190 * November 2011
191 *
192 * .. Scalar Arguments ..
193  INTEGER info, nin, nm, nmats, mmax, nout
194  REAL thresh
195 * ..
196 * .. Array Arguments ..
197  INTEGER iseed( 4 ), iwork( * ), mval( * ), pval( * ),
198  $ qval( * )
199  REAL rwork( * ), theta( * )
200  REAL u1( * ), u2( * ), v1t( * ), v2t( * ),
201  $ work( * ), x( * ), xf( * )
202 * ..
203 *
204 * =====================================================================
205 *
206 * .. Parameters ..
207  INTEGER ntests
208  parameter ( ntests = 15 )
209  INTEGER ntypes
210  parameter ( ntypes = 4 )
211  REAL gapdigit, one, orth, piover2, ten, zero
212  parameter ( gapdigit = 10.0e0, one = 1.0e0,
213  $ orth = 1.0e-4,
214  $ piover2 = 1.57079632679489662e0,
215  $ ten = 10.0e0, zero = 0.0e0 )
216 * ..
217 * .. Local Scalars ..
218  LOGICAL firstt
219  CHARACTER*3 path
220  INTEGER i, iinfo, im, imat, j, ldu1, ldu2, ldv1t,
221  $ ldv2t, ldx, lwork, m, nfail, nrun, nt, p, q, r
222 * ..
223 * .. Local Arrays ..
224  LOGICAL dotype( ntypes )
225  REAL result( ntests )
226 * ..
227 * .. External Subroutines ..
228  EXTERNAL alahdg, alareq, alasum, scsdts, slacsg, slaror,
229  $ slaset
230 * ..
231 * .. Intrinsic Functions ..
232  INTRINSIC abs, min
233 * ..
234 * .. External Functions ..
235  REAL slaran, slarnd
236  EXTERNAL slaran, slarnd
237 * ..
238 * .. Executable Statements ..
239 *
240 * Initialize constants and the random number seed.
241 *
242  path( 1: 3 ) = 'CSD'
243  info = 0
244  nrun = 0
245  nfail = 0
246  firstt = .true.
247  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
248  ldx = mmax
249  ldu1 = mmax
250  ldu2 = mmax
251  ldv1t = mmax
252  ldv2t = mmax
253  lwork = mmax*mmax
254 *
255 * Do for each value of M in MVAL.
256 *
257  DO 30 im = 1, nm
258  m = mval( im )
259  p = pval( im )
260  q = qval( im )
261 *
262  DO 20 imat = 1, ntypes
263 *
264 * Do the tests only if DOTYPE( IMAT ) is true.
265 *
266  IF( .NOT.dotype( imat ) )
267  $ GO TO 20
268 *
269 * Generate X
270 *
271  IF( imat.EQ.1 ) THEN
272  CALL slaror( 'L', 'I', m, m, x, ldx, iseed, work, iinfo )
273  IF( m .NE. 0 .AND. iinfo .NE. 0 ) THEN
274  WRITE( nout, fmt = 9999 ) m, iinfo
275  info = abs( iinfo )
276  GO TO 20
277  END IF
278  ELSE IF( imat.EQ.2 ) THEN
279  r = min( p, m-p, q, m-q )
280  DO i = 1, r
281  theta(i) = piover2 * slarnd( 1, iseed )
282  END DO
283  CALL slacsg( m, p, q, theta, iseed, x, ldx, work )
284  DO i = 1, m
285  DO j = 1, m
286  x(i+(j-1)*ldx) = x(i+(j-1)*ldx) +
287  $ orth*slarnd(2,iseed)
288  END DO
289  END DO
290  ELSE IF( imat.EQ.3 ) THEN
291  r = min( p, m-p, q, m-q )
292  DO i = 1, r+1
293  theta(i) = ten**(-slarnd(1,iseed)*gapdigit)
294  END DO
295  DO i = 2, r+1
296  theta(i) = theta(i-1) + theta(i)
297  END DO
298  DO i = 1, r
299  theta(i) = piover2 * theta(i) / theta(r+1)
300  END DO
301  CALL slacsg( m, p, q, theta, iseed, x, ldx, work )
302  ELSE
303  CALL slaset( 'F', m, m, zero, one, x, ldx )
304  DO i = 1, m
305  j = int( slaran( iseed ) * m ) + 1
306  IF( j .NE. i ) THEN
307  CALL srot( m, x(1+(i-1)*ldx), 1, x(1+(j-1)*ldx), 1,
308  $ zero, one )
309  END IF
310  END DO
311  END IF
312 *
313  nt = 15
314 *
315  CALL scsdts( m, p, q, x, xf, ldx, u1, ldu1, u2, ldu2, v1t,
316  $ ldv1t, v2t, ldv2t, theta, iwork, work, lwork,
317  $ rwork, result )
318 *
319 * Print information about the tests that did not
320 * pass the threshold.
321 *
322  DO 10 i = 1, nt
323  IF( result( i ).GE.thresh ) THEN
324  IF( nfail.EQ.0 .AND. firstt ) THEN
325  firstt = .false.
326  CALL alahdg( nout, path )
327  END IF
328  WRITE( nout, fmt = 9998 )m, p, q, imat, i,
329  $ result( i )
330  nfail = nfail + 1
331  END IF
332  10 CONTINUE
333  nrun = nrun + nt
334  20 CONTINUE
335  30 CONTINUE
336 *
337 * Print a summary of the results.
338 *
339  CALL alasum( path, nout, nfail, nrun, 0 )
340 *
341  9999 FORMAT( ' SLAROR in SCKCSD: M = ', i5, ', INFO = ', i15 )
342  9998 FORMAT( ' M=', i4, ' P=', i4, ', Q=', i4, ', type ', i2,
343  $ ', test ', i2, ', ratio=', g13.6 )
344  RETURN
345 *
346 * End of SCKCSD
347 *
subroutine slacsg(M, P, Q, THETA, ISEED, X, LDX, WORK)
Definition: sckcsd.f:353
subroutine scsdts(M, P, Q, X, XF, LDX, U1, LDU1, U2, LDU2, V1T, LDV1T, V2T, LDV2T, THETA, IWORK, WORK, LWORK, RWORK, RESULT)
SCSDTS
Definition: scsdts.f:231
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine slaror(SIDE, INIT, M, N, A, LDA, ISEED, X, INFO)
SLAROR
Definition: slaror.f:148
subroutine srot(N, SX, INCX, SY, INCY, C, S)
SROT
Definition: srot.f:53
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 slarnd(IDIST, ISEED)
SLARND
Definition: slarnd.f:75
real function slaran(ISEED)
SLARAN
Definition: slaran.f:69
subroutine alahdg(IOUNIT, PATH)
ALAHDG
Definition: alahdg.f:64
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75

Here is the call graph for this function:

Here is the caller graph for this function: