1DGSVJ0(1)LAPACK routine (version 3.2) DGSVJ0(1)
2
3
4
6 DGSVJ0 - is called from DGESVJ as a pre-processor and that is its main
7 purpose
8
10 SUBROUTINE DGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,
11
12 + SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
13
14 IMPLICIT NONE
15
16 INTEGER INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP
17
18 DOUBLE PRECISION EPS, SFMIN, TOL
19
20 CHARACTER*1 JOBV
21
22 DOUBLE PRECISION A( LDA, * ), SVA( N ), D( N ), V( LDV, *
23 ),
24
25 + WORK( LWORK )
26
28 DGSVJ0 is called from DGESVJ as a pre-processor and that is its main
29 purpose. It applies Jacobi rotations in the same way as DGESVJ does,
30 but it does not check convergence (stopping criterion). Few tuning
31 parameters (marked by [TP]) are available for the implementer. Further
32 Details
33 DGSVJ0 is used just to enable SGESVJ to call a simplified version of
34 itself to work on a submatrix of the original matrix.
35 Contributors
36 ~~~~~~~~~~~~
37 Zlatko Drmac (Zagreb, Croatia) and Kresimir Veselic (Hagen, Germany)
38 Bugs, Examples and Comments
39 ~~~~~~~~~~~~~~~~~~~~~~~~~~~
40 Please report all bugs and send interesting test examples and comments
41 to drmac@math.hr. Thank you.
42
44 JOBV (input) CHARACTER*1
45 Specifies whether the output from this procedure is used to
46 compute the matrix V:
47 = 'V': the product of the Jacobi rotations is accumulated by
48 postmulyiplying the N-by-N array V. (See the description of
49 V.) = 'A': the product of the Jacobi rotations is accumulated
50 by postmulyiplying the MV-by-N array V. (See the descriptions
51 of MV and V.) = 'N': the Jacobi rotations are not accumulated.
52
53 M (input) INTEGER
54 The number of rows of the input matrix A. M >= 0.
55
56 N (input) INTEGER
57 The number of columns of the input matrix A. M >= N >= 0.
58
59 A (input/output) REAL array, dimension (LDA,N)
60 On entry, M-by-N matrix A, such that A*diag(D) represents the
61 input matrix. On exit, A_onexit * D_onexit represents the
62 input matrix A*diag(D) post-multiplied by a sequence of Jacobi
63 rotations, where the rotation threshold and the total number of
64 sweeps are given in TOL and NSWEEP, respectively. (See the
65 descriptions of D, TOL and NSWEEP.)
66
67 LDA (input) INTEGER
68 The leading dimension of the array A. LDA >= max(1,M).
69
70 D (input/workspace/output) REAL array, dimension (N)
71 The array D accumulates the scaling factors from the fast
72 scaled Jacobi rotations. On entry, A*diag(D) represents the
73 input matrix. On exit, A_onexit*diag(D_onexit) represents the
74 input matrix post-multiplied by a sequence of Jacobi rotations,
75 where the rotation threshold and the total number of sweeps are
76 given in TOL and NSWEEP, respectively. (See the descriptions
77 of A, TOL and NSWEEP.)
78
79 SVA (input/workspace/output) REAL array, dimension (N)
80 On entry, SVA contains the Euclidean norms of the columns of
81 the matrix A*diag(D). On exit, SVA contains the Euclidean
82 norms of the columns of the matrix onexit*diag(D_onexit).
83
84 MV (input) INTEGER
85 If JOBV .EQ. 'A', then MV rows of V are post-multipled by a
86 sequence of Jacobi rotations. If JOBV = 'N', then MV is not
87 referenced.
88
89 V (input/output) REAL array, dimension (LDV,N)
90 If JOBV .EQ. 'V' then N rows of V are post-multipled by a
91 sequence of Jacobi rotations. If JOBV .EQ. 'A' then MV rows of
92 V are post-multipled by a sequence of Jacobi rotations. If
93 JOBV = 'N', then V is not referenced.
94
95 LDV (input) INTEGER
96 The leading dimension of the array V, LDV >= 1. If JOBV =
97 'V', LDV .GE. N. If JOBV = 'A', LDV .GE. MV.
98
99 EPS (input) INTEGER
100 EPS = SLAMCH('Epsilon')
101
102 SFMIN (input) INTEGER
103 SFMIN = SLAMCH('Safe Minimum')
104
105 TOL (input) REAL
106 TOL is the threshold for Jacobi rotations. For a pair A(:,p),
107 A(:,q) of pivot columns, the Jacobi rotation is
108 applied only if DABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL.
109
110 NSWEEP (input) INTEGER
111 NSWEEP is the number of sweeps of Jacobi rotations to be per‐
112 formed.
113
114 WORK (workspace) REAL array, dimension LWORK.
115
116 LWORK (input) INTEGER
117 LWORK is the dimension of WORK. LWORK .GE. M.
118
119 INFO (output) INTEGER
120 = 0 : successful exit.
121 < 0 : if INFO = -i, then the i-th argument had an illegal value
122
123
124
125 LAPACK routine (version 3.2) November 2008 DGSVJ0(1)