1ZLALSD(1)                LAPACK routine (version 3.1)                ZLALSD(1)
2
3
4

NAME

6       ZLALSD  -  the  singular  value  decomposition  of A to solve the least
7       squares problem of finding X to minimize the  Euclidean  norm  of  each
8       column of A*X-B, where A is N-by-N upper bidiagonal, and X and B are N-
9       by-NRHS
10

SYNOPSIS

12       SUBROUTINE ZLALSD( UPLO, SMLSIZ, N, NRHS, D, E, B,  LDB,  RCOND,  RANK,
13                          WORK, RWORK, IWORK, INFO )
14
15           CHARACTER      UPLO
16
17           INTEGER        INFO, LDB, N, NRHS, RANK, SMLSIZ
18
19           DOUBLE         PRECISION RCOND
20
21           INTEGER        IWORK( * )
22
23           DOUBLE         PRECISION D( * ), E( * ), RWORK( * )
24
25           COMPLEX*16     B( LDB, * ), WORK( * )
26

PURPOSE

28       ZLALSD  uses  the  singular value decomposition of A to solve the least
29       squares problem of finding X to minimize the  Euclidean  norm  of  each
30       column of A*X-B, where A is N-by-N upper bidiagonal, and X and B are N-
31       by-NRHS. The solution X overwrites B.
32
33       The singular values of A smaller than RCOND times the largest  singular
34       value are treated as zero in solving the least squares problem; in this
35       case a minimum norm solution is returned.  The actual  singular  values
36       are returned in D in ascending order.
37
38       This  code makes very mild assumptions about floating point arithmetic.
39       It will work on machines with a guard  digit  in  add/subtract,  or  on
40       those binary machines without guard digits which subtract like the Cray
41       XMP, Cray YMP, Cray C 90, or Cray 2.   It  could  conceivably  fail  on
42       hexadecimal  or  decimal  machines without guard digits, but we know of
43       none.
44
45

ARGUMENTS

47       UPLO   (input) CHARACTER*1
48              = 'U': D and E define an upper bidiagonal matrix.
49              = 'L': D and E define a  lower bidiagonal matrix.
50
51              SMLSIZ (input) INTEGER The maximum size of  the  subproblems  at
52              the bottom of the computation tree.
53
54       N      (input) INTEGER
55              The dimension of the  bidiagonal matrix.  N >= 0.
56
57       NRHS   (input) INTEGER
58              The number of columns of B. NRHS must be at least 1.
59
60       D      (input/output) DOUBLE PRECISION array, dimension (N)
61              On  entry D contains the main diagonal of the bidiagonal matrix.
62              On exit, if INFO = 0, D contains its singular values.
63
64       E      (input/output) DOUBLE PRECISION array, dimension (N-1)
65              Contains the super-diagonal entries of  the  bidiagonal  matrix.
66              On exit, E has been destroyed.
67
68       B      (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
69              On  input,  B contains the right hand sides of the least squares
70              problem. On output, B contains the solution X.
71
72       LDB    (input) INTEGER
73              The leading dimension of B in the calling subprogram.  LDB  must
74              be at least max(1,N).
75
76       RCOND  (input) DOUBLE PRECISION
77              The  singular  values of A less than or equal to RCOND times the
78              largest singular value are treated as zero in solving the  least
79              squares problem. If RCOND is negative, machine precision is used
80              instead.  For example, if diag(S)*X=B  were  the  least  squares
81              problem,  where diag(S) is a diagonal matrix of singular values,
82              the solution would be X(i) = B(i) / S(i) if S(i) is greater than
83              RCOND*max(S),  and  X(i)  =  0  if S(i) is less than or equal to
84              RCOND*max(S).
85
86       RANK   (output) INTEGER
87              The number of singular values of A greater than RCOND times  the
88              largest singular value.
89
90       WORK   (workspace) COMPLEX*16 array, dimension at least
91              (N * NRHS).
92
93       RWORK  (workspace) DOUBLE PRECISION array, dimension at least
94              (9*N  +  2*N*SMLSIZ + 8*N*NLVL + 3*SMLSIZ*NRHS + (SMLSIZ+1)**2),
95              where NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 )
96
97       IWORK  (workspace) INTEGER array, dimension at least
98              (3*N*NLVL + 11*N).
99
100       INFO   (output) INTEGER
101              = 0:  successful exit.
102              < 0:  if INFO = -i, the i-th argument had an illegal value.
103              > 0:  The algorithm failed to compute an  singular  value  while
104              working  on  the  submatrix lying in rows and columns INFO/(N+1)
105              through MOD(INFO,N+1).
106

FURTHER DETAILS

108       Based on contributions by
109          Ming Gu and Ren-Cang Li, Computer Science Division, University of
110            California at Berkeley, USA
111          Osni Marques, LBNL/NERSC, USA
112
113
114
115
116 LAPACK routine (version 3.1)    November 2006                       ZLALSD(1)
Impressum