1DGSVJ1(1)LAPACK routine (version 3.2) DGSVJ1(1)
2
3
4
6 DGSVJ1 - is called from SGESVJ as a pre-processor and that is its main
7 purpose
8
10 SUBROUTINE DGSVJ1( JOBV, M, N, N1, A, LDA, D, SVA, MV, V, LDV,
11
12 + EPS, SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
13
14 IMPLICIT NONE
15
16 DOUBLE PRECISION EPS, SFMIN, TOL
17
18 INTEGER INFO, LDA, LDV, LWORK, M, MV, N, N1, NSWEEP
19
20 CHARACTER*1 JOBV
21
22 DOUBLE PRECISION A( LDA, * ), D( N ), SVA( N ), V( LDV, *
23 ),
24
25 + WORK( LWORK )
26
28 DGSVJ1 is called from SGESVJ as a pre-processor and that is its main
29 purpose. It applies Jacobi rotations in the same way as SGESVJ does,
30 but it targets only particular pivots and it does not check convergence
31 (stopping criterion). Few tunning parameters (marked by [TP]) are
32 available for the implementer.
33 Further Details
34 DGSVJ1 applies few sweeps of Jacobi rotations in the column space of
35 the input M-by-N matrix A. The pivot pairs are taken from the (1,2)
36 off-diagonal block in the corresponding N-by-N Gram matrix A^T * A. The
37 block-entries (tiles) of the (1,2) off-diagonal block are marked by the
38 [x]'s in the following scheme:
39 | * * * [x] [x] [x]|
40 | * * * [x] [x] [x]| Row-cycling in the nblr-by-nblc [x]
41 blocks.
42 | * * * [x] [x] [x]| Row-cyclic pivoting inside each [x]
43 block.
44 |[x] [x] [x] * * * |
45 |[x] [x] [x] * * * |
46 |[x] [x] [x] * * * |
47 In terms of the columns of A, the first N1 columns are rotated
48 'against' the remaining N-N1 columns, trying to increase the angle
49 between the corresponding subspaces. The off-diagonal block is N1-by(N-
50 N1) and it is tiled using quadratic tiles of side KBL. Here, KBL is a
51 tunning parmeter. The number of sweeps is given in NSWEEP and the
52 orthogonality threshold is given in TOL.
53 Contributors
54 ~~~~~~~~~~~~
55 Zlatko Drmac (Zagreb, Croatia) and Kresimir Veselic (Hagen, Germany)
56
58 JOBV (input) CHARACTER*1
59 Specifies whether the output from this procedure is used to
60 compute the matrix V:
61 = 'V': the product of the Jacobi rotations is accumulated by
62 postmulyiplying the N-by-N array V. (See the description of
63 V.) = 'A': the product of the Jacobi rotations is accumulated
64 by postmulyiplying the MV-by-N array V. (See the descriptions
65 of MV and V.) = 'N': the Jacobi rotations are not accumulated.
66
67 M (input) INTEGER
68 The number of rows of the input matrix A. M >= 0.
69
70 N (input) INTEGER
71 The number of columns of the input matrix A. M >= N >= 0.
72
73 N1 (input) INTEGER
74 N1 specifies the 2 x 2 block partition, the first N1 columns
75 are rotated 'against' the remaining N-N1 columns of A.
76
77 A (input/output) REAL array, dimension (LDA,N)
78 On entry, M-by-N matrix A, such that A*diag(D) represents the
79 input matrix. On exit, A_onexit * D_onexit represents the
80 input matrix A*diag(D) post-multiplied by a sequence of Jacobi
81 rotations, where the rotation threshold and the total number of
82 sweeps are given in TOL and NSWEEP, respectively. (See the
83 descriptions of N1, D, TOL and NSWEEP.)
84
85 LDA (input) INTEGER
86 The leading dimension of the array A. LDA >= max(1,M).
87
88 D (input/workspace/output) REAL array, dimension (N)
89 The array D accumulates the scaling factors from the fast
90 scaled Jacobi rotations. On entry, A*diag(D) represents the
91 input matrix. On exit, A_onexit*diag(D_onexit) represents the
92 input matrix post-multiplied by a sequence of Jacobi rotations,
93 where the rotation threshold and the total number of sweeps are
94 given in TOL and NSWEEP, respectively. (See the descriptions
95 of N1, A, TOL and NSWEEP.)
96
97 SVA (input/workspace/output) REAL array, dimension (N)
98 On entry, SVA contains the Euclidean norms of the columns of
99 the matrix A*diag(D). On exit, SVA contains the Euclidean
100 norms of the columns of the matrix onexit*diag(D_onexit).
101
102 MV (input) INTEGER
103 If JOBV .EQ. 'A', then MV rows of V are post-multipled by a
104 sequence of Jacobi rotations. If JOBV = 'N', then MV is not
105 referenced.
106
107 V (input/output) REAL array, dimension (LDV,N)
108 If JOBV .EQ. 'V' then N rows of V are post-multipled by a
109 sequence of Jacobi rotations. If JOBV .EQ. 'A' then MV rows of
110 V are post-multipled by a sequence of Jacobi rotations. If
111 JOBV = 'N', then V is not referenced.
112
113 LDV (input) INTEGER
114 The leading dimension of the array V, LDV >= 1. If JOBV =
115 'V', LDV .GE. N. If JOBV = 'A', LDV .GE. MV.
116
117 EPS (input) INTEGER
118 EPS = SLAMCH('Epsilon')
119
120 SFMIN (input) INTEGER
121 SFMIN = SLAMCH('Safe Minimum')
122
123 TOL (input) REAL
124 TOL is the threshold for Jacobi rotations. For a pair A(:,p),
125 A(:,q) of pivot columns, the Jacobi rotation is
126 applied only if DABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL.
127
128 NSWEEP (input) INTEGER
129 NSWEEP is the number of sweeps of Jacobi rotations to be per‐
130 formed.
131
132 WORK (workspace) REAL array, dimension LWORK.
133
134 LWORK (input) INTEGER
135 LWORK is the dimension of WORK. LWORK .GE. M.
136
137 INFO (output) INTEGER
138 = 0 : successful exit.
139 < 0 : if INFO = -i, then the i-th argument had an illegal value
140
141
142
143 LAPACK routine (version 3.2) November 2008 DGSVJ1(1)