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

ZCKCSD

Purpose:
 ZCKCSD tests ZUNCSD:
        the CSD for an M-by-M unitary 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 DOUBLE PRECISION
          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 COMPLEX*16 array, dimension (MMAX*MMAX)
[out]XF
          XF is COMPLEX*16 array, dimension (MMAX*MMAX)
[out]U1
          U1 is COMPLEX*16 array, dimension (MMAX*MMAX)
[out]U2
          U2 is COMPLEX*16 array, dimension (MMAX*MMAX)
[out]V1T
          V1T is COMPLEX*16 array, dimension (MMAX*MMAX)
[out]V2T
          V2T is COMPLEX*16 array, dimension (MMAX*MMAX)
[out]THETA
          THETA is DOUBLE PRECISION array, dimension (MMAX)
[out]IWORK
          IWORK is INTEGER array, dimension (MMAX)
[out]WORK
          WORK is COMPLEX*16 array
[out]RWORK
          RWORK is DOUBLE PRECISION 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 ZLAROR 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 zckcsd.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  DOUBLE PRECISION thresh
195 * ..
196 * .. Array Arguments ..
197  INTEGER iseed( 4 ), iwork( * ), mval( * ), pval( * ),
198  $ qval( * )
199  DOUBLE PRECISION rwork( * ), theta( * )
200  COMPLEX*16 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  DOUBLE PRECISION gapdigit, orth, piover2, realone, realzero, ten
212  parameter ( gapdigit = 18.0d0, orth = 1.0d-12,
213  $ piover2 = 1.57079632679489662d0,
214  $ realone = 1.0d0, realzero = 0.0d0,
215  $ ten = 10.0d0 )
216  COMPLEX*16 one, zero
217  parameter ( one = (1.0d0,0.0d0), zero = (0.0d0,0.0d0) )
218 * ..
219 * .. Local Scalars ..
220  LOGICAL firstt
221  CHARACTER*3 path
222  INTEGER i, iinfo, im, imat, j, ldu1, ldu2, ldv1t,
223  $ ldv2t, ldx, lwork, m, nfail, nrun, nt, p, q, r
224 * ..
225 * .. Local Arrays ..
226  LOGICAL dotype( ntypes )
227  DOUBLE PRECISION result( ntests )
228 * ..
229 * .. External Subroutines ..
230  EXTERNAL alahdg, alareq, alasum, zcsdts, zlacsg, zlaror,
231  $ zlaset
232 * ..
233 * .. Intrinsic Functions ..
234  INTRINSIC abs, min
235 * ..
236 * .. External Functions ..
237  DOUBLE PRECISION dlaran, dlarnd
238  EXTERNAL dlaran, dlarnd
239 * ..
240 * .. Executable Statements ..
241 *
242 * Initialize constants and the random number seed.
243 *
244  path( 1: 3 ) = 'CSD'
245  info = 0
246  nrun = 0
247  nfail = 0
248  firstt = .true.
249  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
250  ldx = mmax
251  ldu1 = mmax
252  ldu2 = mmax
253  ldv1t = mmax
254  ldv2t = mmax
255  lwork = mmax*mmax
256 *
257 * Do for each value of M in MVAL.
258 *
259  DO 30 im = 1, nm
260  m = mval( im )
261  p = pval( im )
262  q = qval( im )
263 *
264  DO 20 imat = 1, ntypes
265 *
266 * Do the tests only if DOTYPE( IMAT ) is true.
267 *
268  IF( .NOT.dotype( imat ) )
269  $ GO TO 20
270 *
271 * Generate X
272 *
273  IF( imat.EQ.1 ) THEN
274  CALL zlaror( 'L', 'I', m, m, x, ldx, iseed, work, iinfo )
275  IF( m .NE. 0 .AND. iinfo .NE. 0 ) THEN
276  WRITE( nout, fmt = 9999 ) m, iinfo
277  info = abs( iinfo )
278  GO TO 20
279  END IF
280  ELSE IF( imat.EQ.2 ) THEN
281  r = min( p, m-p, q, m-q )
282  DO i = 1, r
283  theta(i) = piover2 * dlarnd( 1, iseed )
284  END DO
285  CALL zlacsg( m, p, q, theta, iseed, x, ldx, work )
286  DO i = 1, m
287  DO j = 1, m
288  x(i+(j-1)*ldx) = x(i+(j-1)*ldx) +
289  $ orth*dlarnd(2,iseed)
290  END DO
291  END DO
292  ELSE IF( imat.EQ.3 ) THEN
293  r = min( p, m-p, q, m-q )
294  DO i = 1, r+1
295  theta(i) = ten**(-dlarnd(1,iseed)*gapdigit)
296  END DO
297  DO i = 2, r+1
298  theta(i) = theta(i-1) + theta(i)
299  END DO
300  DO i = 1, r
301  theta(i) = piover2 * theta(i) / theta(r+1)
302  END DO
303  CALL zlacsg( m, p, q, theta, iseed, x, ldx, work )
304  ELSE
305  CALL zlaset( 'F', m, m, zero, one, x, ldx )
306  DO i = 1, m
307  j = int( dlaran( iseed ) * m ) + 1
308  IF( j .NE. i ) THEN
309  CALL zdrot( m, x(1+(i-1)*ldx), 1, x(1+(j-1)*ldx),
310  $ 1, realzero, realone )
311  END IF
312  END DO
313  END IF
314 *
315  nt = 15
316 *
317  CALL zcsdts( m, p, q, x, xf, ldx, u1, ldu1, u2, ldu2, v1t,
318  $ ldv1t, v2t, ldv2t, theta, iwork, work, lwork,
319  $ rwork, result )
320 *
321 * Print information about the tests that did not
322 * pass the threshold.
323 *
324  DO 10 i = 1, nt
325  IF( result( i ).GE.thresh ) THEN
326  IF( nfail.EQ.0 .AND. firstt ) THEN
327  firstt = .false.
328  CALL alahdg( nout, path )
329  END IF
330  WRITE( nout, fmt = 9998 )m, p, q, imat, i,
331  $ result( i )
332  nfail = nfail + 1
333  END IF
334  10 CONTINUE
335  nrun = nrun + nt
336  20 CONTINUE
337  30 CONTINUE
338 *
339 * Print a summary of the results.
340 *
341  CALL alasum( path, nout, nfail, nrun, 0 )
342 *
343  9999 FORMAT( ' ZLAROR in ZCKCSD: M = ', i5, ', INFO = ', i15 )
344  9998 FORMAT( ' M=', i4, ' P=', i4, ', Q=', i4, ', type ', i2,
345  $ ', test ', i2, ', ratio=', g13.6 )
346  RETURN
347 *
348 * End of ZCKCSD
349 *
subroutine zcsdts(M, P, Q, X, XF, LDX, U1, LDU1, U2, LDU2, V1T, LDV1T, V2T, LDV2T, THETA, IWORK, WORK, LWORK, RWORK, RESULT)
ZCSDTS
Definition: zcsdts.f:231
subroutine zlaror(SIDE, INIT, M, N, A, LDA, ISEED, X, INFO)
ZLAROR
Definition: zlaror.f:160
subroutine zlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: zlaset.f:108
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine zdrot(N, CX, INCX, CY, INCY, C, S)
ZDROT
Definition: zdrot.f:100
double precision function dlarnd(IDIST, ISEED)
DLARND
Definition: dlarnd.f:75
double precision function dlaran(ISEED)
DLARAN
Definition: dlaran.f:69
subroutine zlacsg(M, P, Q, THETA, ISEED, X, LDX, WORK)
Definition: zckcsd.f:355
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: