1SGSVJ1(1)LAPACK routine (version 3.2)                                 SGSVJ1(1)
2
3
4

NAME

6       SGSVJ1  - is called from SGESVJ as a pre-processor and that is its main
7       purpose
8

SYNOPSIS

10       SUBROUTINE SGSVJ1( 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           REAL           EPS, SFMIN, TOL
17
18           INTEGER        INFO, LDA, LDV, LWORK, M, MV, N, N1, NSWEEP
19
20           CHARACTER*1    JOBV
21
22           REAL           A( LDA, * ), D( N ), SVA( N ), V( LDV, * ),
23
24           +              WORK( LWORK )
25

PURPOSE

27       SGSVJ1 is called from SGESVJ as a pre-processor and that  is  its  main
28       purpose.  It  applies  Jacobi rotations in the same way as SGESVJ does,
29       but it targets only particular pivots and it does not check convergence
30       (stopping  criterion).  Few  tunning  parameters  (marked  by [TP]) are
31       available for the implementer.
32       Further Details
33       SGSVJ1 applies few sweeps of Jacobi rotations in the  column  space  of
34       the  input  M-by-N  matrix  A. The pivot pairs are taken from the (1,2)
35       off-diagonal block in the corresponding N-by-N Gram matrix A^T * A. The
36       block-entries (tiles) of the (1,2) off-diagonal block are marked by the
37       [x]'s in the following scheme:
38          | *   *   * [x] [x] [x]|
39          | *   *   * [x] [x] [x]|     Row-cycling  in  the  nblr-by-nblc  [x]
40       blocks.
41          |  *    *    *  [x]  [x] [x]|    Row-cyclic pivoting inside each [x]
42       block.
43          |[x] [x] [x] *   *   * |
44          |[x] [x] [x] *   *   * |
45          |[x] [x] [x] *   *   * |
46       In terms of the  columns  of  A,  the  first  N1  columns  are  rotated
47       'against'  the  remaining  N-N1  columns,  trying to increase the angle
48       between the corresponding subspaces. The off-diagonal block is N1-by(N-
49       N1)  and  it is tiled using quadratic tiles of side KBL. Here, KBL is a
50       tunning parmeter.  The number of sweeps is  given  in  NSWEEP  and  the
51       orthogonality threshold is given in TOL.
52       Contributors
53       ~~~~~~~~~~~~
54       Zlatko Drmac (Zagreb, Croatia) and Kresimir Veselic (Hagen, Germany)
55

ARGUMENTS

57       JOBV    (input) CHARACTER*1
58               Specifies  whether  the  output  from this procedure is used to
59               compute the matrix V:
60               = 'V': the product of the Jacobi rotations  is  accumulated  by
61               postmulyiplying  the  N-by-N  array V.  (See the description of
62               V.)  = 'A': the product of the Jacobi rotations is  accumulated
63               by  postmulyiplying the MV-by-N array V.  (See the descriptions
64               of MV and V.)  = 'N': the Jacobi rotations are not accumulated.
65
66       M       (input) INTEGER
67               The number of rows of the input matrix A.  M >= 0.
68
69       N       (input) INTEGER
70               The number of columns of the input matrix A.  M >= N >= 0.
71
72       N1      (input) INTEGER
73               N1 specifies the 2 x 2 block partition, the  first  N1  columns
74               are rotated 'against' the remaining N-N1 columns of A.
75
76       A       (input/output) REAL array, dimension (LDA,N)
77               On  entry,  M-by-N matrix A, such that A*diag(D) represents the
78               input matrix.  On exit,  A_onexit  *  D_onexit  represents  the
79               input  matrix A*diag(D) post-multiplied by a sequence of Jacobi
80               rotations, where the rotation threshold and the total number of
81               sweeps  are  given  in  TOL and NSWEEP, respectively.  (See the
82               descriptions of N1, D, TOL and NSWEEP.)
83
84       LDA     (input) INTEGER
85               The leading dimension of the array A.  LDA >= max(1,M).
86
87       D       (input/workspace/output) REAL array, dimension (N)
88               The array D accumulates  the  scaling  factors  from  the  fast
89               scaled  Jacobi  rotations.   On entry, A*diag(D) represents the
90               input matrix.  On exit, A_onexit*diag(D_onexit) represents  the
91               input matrix post-multiplied by a sequence of Jacobi rotations,
92               where the rotation threshold and the total number of sweeps are
93               given  in  TOL and NSWEEP, respectively.  (See the descriptions
94               of N1, A, TOL and NSWEEP.)
95
96       SVA     (input/workspace/output) REAL array, dimension (N)
97               On entry, SVA contains the Euclidean norms of  the  columns  of
98               the  matrix  A*diag(D).   On  exit,  SVA contains the Euclidean
99               norms of the columns of the matrix onexit*diag(D_onexit).
100
101       MV      (input) INTEGER
102               If JOBV .EQ. 'A', then MV rows of V  are  post-multipled  by  a
103               sequence  of Jacobi rotations.  If JOBV = 'N',   then MV is not
104               referenced.
105
106       V       (input/output) REAL array, dimension (LDV,N)
107               If JOBV .EQ. 'V' then N rows  of  V  are  post-multipled  by  a
108               sequence of Jacobi rotations.  If JOBV .EQ. 'A' then MV rows of
109               V are post-multipled by a sequence  of  Jacobi  rotations.   If
110               JOBV = 'N',   then V is not referenced.
111
112       LDV     (input) INTEGER
113               The  leading  dimension  of  the array V,  LDV >= 1.  If JOBV =
114               'V', LDV .GE. N.  If JOBV = 'A', LDV .GE. MV.
115
116       EPS     (input) INTEGER
117               EPS = SLAMCH('Epsilon')
118
119       SFMIN   (input) INTEGER
120               SFMIN = SLAMCH('Safe Minimum')
121
122       TOL     (input) REAL
123               TOL is the threshold for Jacobi rotations. For a  pair  A(:,p),
124               A(:,q) of pivot columns, the Jacobi rotation is
125               applied only if ABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL.
126
127       NSWEEP  (input) INTEGER
128               NSWEEP  is  the number of sweeps of Jacobi rotations to be per‐
129               formed.
130
131       WORK    (workspace) REAL array, dimension LWORK.
132
133       LWORK   (input) INTEGER
134               LWORK is the dimension of WORK. LWORK .GE. M.
135
136       INFO    (output) INTEGER
137               = 0 : successful exit.
138               < 0 : if INFO = -i, then the i-th argument had an illegal value
139
140
141
142 LAPACK routine (version 3.2)    November 2008                       SGSVJ1(1)
Impressum