001:       SUBROUTINE SLAED0( ICOMPQ, QSIZ, N, D, E, Q, LDQ, QSTORE, LDQS,
002:      $                   WORK, IWORK, INFO )
003: *
004: *  -- LAPACK routine (version 3.2) --
005: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            ICOMPQ, INFO, LDQ, LDQS, N, QSIZ
010: *     ..
011: *     .. Array Arguments ..
012:       INTEGER            IWORK( * )
013:       REAL               D( * ), E( * ), Q( LDQ, * ), QSTORE( LDQS, * ),
014:      $                   WORK( * )
015: *     ..
016: *
017: *  Purpose
018: *  =======
019: *
020: *  SLAED0 computes all eigenvalues and corresponding eigenvectors of a
021: *  symmetric tridiagonal matrix using the divide and conquer method.
022: *
023: *  Arguments
024: *  =========
025: *
026: *  ICOMPQ  (input) INTEGER
027: *          = 0:  Compute eigenvalues only.
028: *          = 1:  Compute eigenvectors of original dense symmetric matrix
029: *                also.  On entry, Q contains the orthogonal matrix used
030: *                to reduce the original matrix to tridiagonal form.
031: *          = 2:  Compute eigenvalues and eigenvectors of tridiagonal
032: *                matrix.
033: *
034: *  QSIZ   (input) INTEGER
035: *         The dimension of the orthogonal matrix used to reduce
036: *         the full matrix to tridiagonal form.  QSIZ >= N if ICOMPQ = 1.
037: *
038: *  N      (input) INTEGER
039: *         The dimension of the symmetric tridiagonal matrix.  N >= 0.
040: *
041: *  D      (input/output) REAL array, dimension (N)
042: *         On entry, the main diagonal of the tridiagonal matrix.
043: *         On exit, its eigenvalues.
044: *
045: *  E      (input) REAL array, dimension (N-1)
046: *         The off-diagonal elements of the tridiagonal matrix.
047: *         On exit, E has been destroyed.
048: *
049: *  Q      (input/output) REAL array, dimension (LDQ, N)
050: *         On entry, Q must contain an N-by-N orthogonal matrix.
051: *         If ICOMPQ = 0    Q is not referenced.
052: *         If ICOMPQ = 1    On entry, Q is a subset of the columns of the
053: *                          orthogonal matrix used to reduce the full
054: *                          matrix to tridiagonal form corresponding to
055: *                          the subset of the full matrix which is being
056: *                          decomposed at this time.
057: *         If ICOMPQ = 2    On entry, Q will be the identity matrix.
058: *                          On exit, Q contains the eigenvectors of the
059: *                          tridiagonal matrix.
060: *
061: *  LDQ    (input) INTEGER
062: *         The leading dimension of the array Q.  If eigenvectors are
063: *         desired, then  LDQ >= max(1,N).  In any case,  LDQ >= 1.
064: *
065: *  QSTORE (workspace) REAL array, dimension (LDQS, N)
066: *         Referenced only when ICOMPQ = 1.  Used to store parts of
067: *         the eigenvector matrix when the updating matrix multiplies
068: *         take place.
069: *
070: *  LDQS   (input) INTEGER
071: *         The leading dimension of the array QSTORE.  If ICOMPQ = 1,
072: *         then  LDQS >= max(1,N).  In any case,  LDQS >= 1.
073: *
074: *  WORK   (workspace) REAL array,
075: *         If ICOMPQ = 0 or 1, the dimension of WORK must be at least
076: *                     1 + 3*N + 2*N*lg N + 2*N**2
077: *                     ( lg( N ) = smallest integer k
078: *                                 such that 2^k >= N )
079: *         If ICOMPQ = 2, the dimension of WORK must be at least
080: *                     4*N + N**2.
081: *
082: *  IWORK  (workspace) INTEGER array,
083: *         If ICOMPQ = 0 or 1, the dimension of IWORK must be at least
084: *                        6 + 6*N + 5*N*lg N.
085: *                        ( lg( N ) = smallest integer k
086: *                                    such that 2^k >= N )
087: *         If ICOMPQ = 2, the dimension of IWORK must be at least
088: *                        3 + 5*N.
089: *
090: *  INFO   (output) INTEGER
091: *          = 0:  successful exit.
092: *          < 0:  if INFO = -i, the i-th argument had an illegal value.
093: *          > 0:  The algorithm failed to compute an eigenvalue while
094: *                working on the submatrix lying in rows and columns
095: *                INFO/(N+1) through mod(INFO,N+1).
096: *
097: *  Further Details
098: *  ===============
099: *
100: *  Based on contributions by
101: *     Jeff Rutter, Computer Science Division, University of California
102: *     at Berkeley, USA
103: *
104: *  =====================================================================
105: *
106: *     .. Parameters ..
107:       REAL               ZERO, ONE, TWO
108:       PARAMETER          ( ZERO = 0.E0, ONE = 1.E0, TWO = 2.E0 )
109: *     ..
110: *     .. Local Scalars ..
111:       INTEGER            CURLVL, CURPRB, CURR, I, IGIVCL, IGIVNM,
112:      $                   IGIVPT, INDXQ, IPERM, IPRMPT, IQ, IQPTR, IWREM,
113:      $                   J, K, LGN, MATSIZ, MSD2, SMLSIZ, SMM1, SPM1,
114:      $                   SPM2, SUBMAT, SUBPBS, TLVLS
115:       REAL               TEMP
116: *     ..
117: *     .. External Subroutines ..
118:       EXTERNAL           SCOPY, SGEMM, SLACPY, SLAED1, SLAED7, SSTEQR,
119:      $                   XERBLA
120: *     ..
121: *     .. External Functions ..
122:       INTEGER            ILAENV
123:       EXTERNAL           ILAENV
124: *     ..
125: *     .. Intrinsic Functions ..
126:       INTRINSIC          ABS, INT, LOG, MAX, REAL
127: *     ..
128: *     .. Executable Statements ..
129: *
130: *     Test the input parameters.
131: *
132:       INFO = 0
133: *
134:       IF( ICOMPQ.LT.0 .OR. ICOMPQ.GT.2 ) THEN
135:          INFO = -1
136:       ELSE IF( ( ICOMPQ.EQ.1 ) .AND. ( QSIZ.LT.MAX( 0, N ) ) ) THEN
137:          INFO = -2
138:       ELSE IF( N.LT.0 ) THEN
139:          INFO = -3
140:       ELSE IF( LDQ.LT.MAX( 1, N ) ) THEN
141:          INFO = -7
142:       ELSE IF( LDQS.LT.MAX( 1, N ) ) THEN
143:          INFO = -9
144:       END IF
145:       IF( INFO.NE.0 ) THEN
146:          CALL XERBLA( 'SLAED0', -INFO )
147:          RETURN
148:       END IF
149: *
150: *     Quick return if possible
151: *
152:       IF( N.EQ.0 )
153:      $   RETURN
154: *
155:       SMLSIZ = ILAENV( 9, 'SLAED0', ' ', 0, 0, 0, 0 )
156: *
157: *     Determine the size and placement of the submatrices, and save in
158: *     the leading elements of IWORK.
159: *
160:       IWORK( 1 ) = N
161:       SUBPBS = 1
162:       TLVLS = 0
163:    10 CONTINUE
164:       IF( IWORK( SUBPBS ).GT.SMLSIZ ) THEN
165:          DO 20 J = SUBPBS, 1, -1
166:             IWORK( 2*J ) = ( IWORK( J )+1 ) / 2
167:             IWORK( 2*J-1 ) = IWORK( J ) / 2
168:    20    CONTINUE
169:          TLVLS = TLVLS + 1
170:          SUBPBS = 2*SUBPBS
171:          GO TO 10
172:       END IF
173:       DO 30 J = 2, SUBPBS
174:          IWORK( J ) = IWORK( J ) + IWORK( J-1 )
175:    30 CONTINUE
176: *
177: *     Divide the matrix into SUBPBS submatrices of size at most SMLSIZ+1
178: *     using rank-1 modifications (cuts).
179: *
180:       SPM1 = SUBPBS - 1
181:       DO 40 I = 1, SPM1
182:          SUBMAT = IWORK( I ) + 1
183:          SMM1 = SUBMAT - 1
184:          D( SMM1 ) = D( SMM1 ) - ABS( E( SMM1 ) )
185:          D( SUBMAT ) = D( SUBMAT ) - ABS( E( SMM1 ) )
186:    40 CONTINUE
187: *
188:       INDXQ = 4*N + 3
189:       IF( ICOMPQ.NE.2 ) THEN
190: *
191: *        Set up workspaces for eigenvalues only/accumulate new vectors
192: *        routine
193: *
194:          TEMP = LOG( REAL( N ) ) / LOG( TWO )
195:          LGN = INT( TEMP )
196:          IF( 2**LGN.LT.N )
197:      $      LGN = LGN + 1
198:          IF( 2**LGN.LT.N )
199:      $      LGN = LGN + 1
200:          IPRMPT = INDXQ + N + 1
201:          IPERM = IPRMPT + N*LGN
202:          IQPTR = IPERM + N*LGN
203:          IGIVPT = IQPTR + N + 2
204:          IGIVCL = IGIVPT + N*LGN
205: *
206:          IGIVNM = 1
207:          IQ = IGIVNM + 2*N*LGN
208:          IWREM = IQ + N**2 + 1
209: *
210: *        Initialize pointers
211: *
212:          DO 50 I = 0, SUBPBS
213:             IWORK( IPRMPT+I ) = 1
214:             IWORK( IGIVPT+I ) = 1
215:    50    CONTINUE
216:          IWORK( IQPTR ) = 1
217:       END IF
218: *
219: *     Solve each submatrix eigenproblem at the bottom of the divide and
220: *     conquer tree.
221: *
222:       CURR = 0
223:       DO 70 I = 0, SPM1
224:          IF( I.EQ.0 ) THEN
225:             SUBMAT = 1
226:             MATSIZ = IWORK( 1 )
227:          ELSE
228:             SUBMAT = IWORK( I ) + 1
229:             MATSIZ = IWORK( I+1 ) - IWORK( I )
230:          END IF
231:          IF( ICOMPQ.EQ.2 ) THEN
232:             CALL SSTEQR( 'I', MATSIZ, D( SUBMAT ), E( SUBMAT ),
233:      $                   Q( SUBMAT, SUBMAT ), LDQ, WORK, INFO )
234:             IF( INFO.NE.0 )
235:      $         GO TO 130
236:          ELSE
237:             CALL SSTEQR( 'I', MATSIZ, D( SUBMAT ), E( SUBMAT ),
238:      $                   WORK( IQ-1+IWORK( IQPTR+CURR ) ), MATSIZ, WORK,
239:      $                   INFO )
240:             IF( INFO.NE.0 )
241:      $         GO TO 130
242:             IF( ICOMPQ.EQ.1 ) THEN
243:                CALL SGEMM( 'N', 'N', QSIZ, MATSIZ, MATSIZ, ONE,
244:      $                     Q( 1, SUBMAT ), LDQ, WORK( IQ-1+IWORK( IQPTR+
245:      $                     CURR ) ), MATSIZ, ZERO, QSTORE( 1, SUBMAT ),
246:      $                     LDQS )
247:             END IF
248:             IWORK( IQPTR+CURR+1 ) = IWORK( IQPTR+CURR ) + MATSIZ**2
249:             CURR = CURR + 1
250:          END IF
251:          K = 1
252:          DO 60 J = SUBMAT, IWORK( I+1 )
253:             IWORK( INDXQ+J ) = K
254:             K = K + 1
255:    60    CONTINUE
256:    70 CONTINUE
257: *
258: *     Successively merge eigensystems of adjacent submatrices
259: *     into eigensystem for the corresponding larger matrix.
260: *
261: *     while ( SUBPBS > 1 )
262: *
263:       CURLVL = 1
264:    80 CONTINUE
265:       IF( SUBPBS.GT.1 ) THEN
266:          SPM2 = SUBPBS - 2
267:          DO 90 I = 0, SPM2, 2
268:             IF( I.EQ.0 ) THEN
269:                SUBMAT = 1
270:                MATSIZ = IWORK( 2 )
271:                MSD2 = IWORK( 1 )
272:                CURPRB = 0
273:             ELSE
274:                SUBMAT = IWORK( I ) + 1
275:                MATSIZ = IWORK( I+2 ) - IWORK( I )
276:                MSD2 = MATSIZ / 2
277:                CURPRB = CURPRB + 1
278:             END IF
279: *
280: *     Merge lower order eigensystems (of size MSD2 and MATSIZ - MSD2)
281: *     into an eigensystem of size MATSIZ.
282: *     SLAED1 is used only for the full eigensystem of a tridiagonal
283: *     matrix.
284: *     SLAED7 handles the cases in which eigenvalues only or eigenvalues
285: *     and eigenvectors of a full symmetric matrix (which was reduced to
286: *     tridiagonal form) are desired.
287: *
288:             IF( ICOMPQ.EQ.2 ) THEN
289:                CALL SLAED1( MATSIZ, D( SUBMAT ), Q( SUBMAT, SUBMAT ),
290:      $                      LDQ, IWORK( INDXQ+SUBMAT ),
291:      $                      E( SUBMAT+MSD2-1 ), MSD2, WORK,
292:      $                      IWORK( SUBPBS+1 ), INFO )
293:             ELSE
294:                CALL SLAED7( ICOMPQ, MATSIZ, QSIZ, TLVLS, CURLVL, CURPRB,
295:      $                      D( SUBMAT ), QSTORE( 1, SUBMAT ), LDQS,
296:      $                      IWORK( INDXQ+SUBMAT ), E( SUBMAT+MSD2-1 ),
297:      $                      MSD2, WORK( IQ ), IWORK( IQPTR ),
298:      $                      IWORK( IPRMPT ), IWORK( IPERM ),
299:      $                      IWORK( IGIVPT ), IWORK( IGIVCL ),
300:      $                      WORK( IGIVNM ), WORK( IWREM ),
301:      $                      IWORK( SUBPBS+1 ), INFO )
302:             END IF
303:             IF( INFO.NE.0 )
304:      $         GO TO 130
305:             IWORK( I / 2+1 ) = IWORK( I+2 )
306:    90    CONTINUE
307:          SUBPBS = SUBPBS / 2
308:          CURLVL = CURLVL + 1
309:          GO TO 80
310:       END IF
311: *
312: *     end while
313: *
314: *     Re-merge the eigenvalues/vectors which were deflated at the final
315: *     merge step.
316: *
317:       IF( ICOMPQ.EQ.1 ) THEN
318:          DO 100 I = 1, N
319:             J = IWORK( INDXQ+I )
320:             WORK( I ) = D( J )
321:             CALL SCOPY( QSIZ, QSTORE( 1, J ), 1, Q( 1, I ), 1 )
322:   100    CONTINUE
323:          CALL SCOPY( N, WORK, 1, D, 1 )
324:       ELSE IF( ICOMPQ.EQ.2 ) THEN
325:          DO 110 I = 1, N
326:             J = IWORK( INDXQ+I )
327:             WORK( I ) = D( J )
328:             CALL SCOPY( N, Q( 1, J ), 1, WORK( N*I+1 ), 1 )
329:   110    CONTINUE
330:          CALL SCOPY( N, WORK, 1, D, 1 )
331:          CALL SLACPY( 'A', N, N, WORK( N+1 ), N, Q, LDQ )
332:       ELSE
333:          DO 120 I = 1, N
334:             J = IWORK( INDXQ+I )
335:             WORK( I ) = D( J )
336:   120    CONTINUE
337:          CALL SCOPY( N, WORK, 1, D, 1 )
338:       END IF
339:       GO TO 140
340: *
341:   130 CONTINUE
342:       INFO = SUBMAT*( N+1 ) + SUBMAT + MATSIZ - 1
343: *
344:   140 CONTINUE
345:       RETURN
346: *
347: *     End of SLAED0
348: *
349:       END
350: