LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsytrd_2stage.f
Go to the documentation of this file.
1*> \brief \b DSYTRD_2STAGE
2*
3* @generated from zhetrd_2stage.f, fortran z -> d, Sun Nov 6 19:34:06 2016
4*
5* =========== DOCUMENTATION ===========
6*
7* Online html documentation available at
8* http://www.netlib.org/lapack/explore-html/
9*
10*> \htmlonly
11*> Download DSYTRD_2STAGE + dependencies
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsytrd_2stage.f">
13*> [TGZ]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsytrd_2stage.f">
15*> [ZIP]</a>
16*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsytrd_2stage.f">
17*> [TXT]</a>
18*> \endhtmlonly
19*
20* Definition:
21* ===========
22*
23* SUBROUTINE DSYTRD_2STAGE( VECT, UPLO, N, A, LDA, D, E, TAU,
24* HOUS2, LHOUS2, WORK, LWORK, INFO )
25*
26* IMPLICIT NONE
27*
28* .. Scalar Arguments ..
29* CHARACTER VECT, UPLO
30* INTEGER N, LDA, LWORK, LHOUS2, INFO
31* ..
32* .. Array Arguments ..
33* DOUBLE PRECISION D( * ), E( * )
34* DOUBLE PRECISION A( LDA, * ), TAU( * ),
35* HOUS2( * ), WORK( * )
36* ..
37*
38*
39*> \par Purpose:
40* =============
41*>
42*> \verbatim
43*>
44*> DSYTRD_2STAGE reduces a real symmetric matrix A to real symmetric
45*> tridiagonal form T by a orthogonal similarity transformation:
46*> Q1**T Q2**T* A * Q2 * Q1 = T.
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] VECT
53*> \verbatim
54*> VECT is CHARACTER*1
55*> = 'N': No need for the Housholder representation,
56*> in particular for the second stage (Band to
57*> tridiagonal) and thus LHOUS2 is of size max(1, 4*N);
58*> = 'V': the Householder representation is needed to
59*> either generate Q1 Q2 or to apply Q1 Q2,
60*> then LHOUS2 is to be queried and computed.
61*> (NOT AVAILABLE IN THIS RELEASE).
62*> \endverbatim
63*>
64*> \param[in] UPLO
65*> \verbatim
66*> UPLO is CHARACTER*1
67*> = 'U': Upper triangle of A is stored;
68*> = 'L': Lower triangle of A is stored.
69*> \endverbatim
70*>
71*> \param[in] N
72*> \verbatim
73*> N is INTEGER
74*> The order of the matrix A. N >= 0.
75*> \endverbatim
76*>
77*> \param[in,out] A
78*> \verbatim
79*> A is DOUBLE PRECISION array, dimension (LDA,N)
80*> On entry, the symmetric matrix A. If UPLO = 'U', the leading
81*> N-by-N upper triangular part of A contains the upper
82*> triangular part of the matrix A, and the strictly lower
83*> triangular part of A is not referenced. If UPLO = 'L', the
84*> leading N-by-N lower triangular part of A contains the lower
85*> triangular part of the matrix A, and the strictly upper
86*> triangular part of A is not referenced.
87*> On exit, if UPLO = 'U', the band superdiagonal
88*> of A are overwritten by the corresponding elements of the
89*> internal band-diagonal matrix AB, and the elements above
90*> the KD superdiagonal, with the array TAU, represent the orthogonal
91*> matrix Q1 as a product of elementary reflectors; if UPLO
92*> = 'L', the diagonal and band subdiagonal of A are over-
93*> written by the corresponding elements of the internal band-diagonal
94*> matrix AB, and the elements below the KD subdiagonal, with
95*> the array TAU, represent the orthogonal matrix Q1 as a product
96*> of elementary reflectors. See Further Details.
97*> \endverbatim
98*>
99*> \param[in] LDA
100*> \verbatim
101*> LDA is INTEGER
102*> The leading dimension of the array A. LDA >= max(1,N).
103*> \endverbatim
104*>
105*> \param[out] D
106*> \verbatim
107*> D is DOUBLE PRECISION array, dimension (N)
108*> The diagonal elements of the tridiagonal matrix T.
109*> \endverbatim
110*>
111*> \param[out] E
112*> \verbatim
113*> E is DOUBLE PRECISION array, dimension (N-1)
114*> The off-diagonal elements of the tridiagonal matrix T.
115*> \endverbatim
116*>
117*> \param[out] TAU
118*> \verbatim
119*> TAU is DOUBLE PRECISION array, dimension (N-KD)
120*> The scalar factors of the elementary reflectors of
121*> the first stage (see Further Details).
122*> \endverbatim
123*>
124*> \param[out] HOUS2
125*> \verbatim
126*> HOUS2 is DOUBLE PRECISION array, dimension (LHOUS2)
127*> Stores the Householder representation of the stage2
128*> band to tridiagonal.
129*> \endverbatim
130*>
131*> \param[in] LHOUS2
132*> \verbatim
133*> LHOUS2 is INTEGER
134*> The dimension of the array HOUS2.
135*> If LWORK = -1, or LHOUS2 = -1,
136*> then a query is assumed; the routine
137*> only calculates the optimal size of the HOUS2 array, returns
138*> this value as the first entry of the HOUS2 array, and no error
139*> message related to LHOUS2 is issued by XERBLA.
140*> If VECT='N', LHOUS2 = max(1, 4*n);
141*> if VECT='V', option not yet available.
142*> \endverbatim
143*>
144*> \param[out] WORK
145*> \verbatim
146*> WORK is DOUBLE PRECISION array, dimension (LWORK)
147*> \endverbatim
148*>
149*> \param[in] LWORK
150*> \verbatim
151*> LWORK is INTEGER
152*> The dimension of the array WORK. LWORK = MAX(1, dimension)
153*> If LWORK = -1, or LHOUS2=-1,
154*> then a workspace query is assumed; the routine
155*> only calculates the optimal size of the WORK array, returns
156*> this value as the first entry of the WORK array, and no error
157*> message related to LWORK is issued by XERBLA.
158*> LWORK = MAX(1, dimension) where
159*> dimension = max(stage1,stage2) + (KD+1)*N
160*> = N*KD + N*max(KD+1,FACTOPTNB)
161*> + max(2*KD*KD, KD*NTHREADS)
162*> + (KD+1)*N
163*> where KD is the blocking size of the reduction,
164*> FACTOPTNB is the blocking used by the QR or LQ
165*> algorithm, usually FACTOPTNB=128 is a good choice
166*> NTHREADS is the number of threads used when
167*> openMP compilation is enabled, otherwise =1.
168*> \endverbatim
169*>
170*> \param[out] INFO
171*> \verbatim
172*> INFO is INTEGER
173*> = 0: successful exit
174*> < 0: if INFO = -i, the i-th argument had an illegal value
175*> \endverbatim
176*
177* Authors:
178* ========
179*
180*> \author Univ. of Tennessee
181*> \author Univ. of California Berkeley
182*> \author Univ. of Colorado Denver
183*> \author NAG Ltd.
184*
185*> \ingroup hetrd_2stage
186*
187*> \par Further Details:
188* =====================
189*>
190*> \verbatim
191*>
192*> Implemented by Azzam Haidar.
193*>
194*> All details are available on technical report, SC11, SC13 papers.
195*>
196*> Azzam Haidar, Hatem Ltaief, and Jack Dongarra.
197*> Parallel reduction to condensed forms for symmetric eigenvalue problems
198*> using aggregated fine-grained and memory-aware kernels. In Proceedings
199*> of 2011 International Conference for High Performance Computing,
200*> Networking, Storage and Analysis (SC '11), New York, NY, USA,
201*> Article 8 , 11 pages.
202*> http://doi.acm.org/10.1145/2063384.2063394
203*>
204*> A. Haidar, J. Kurzak, P. Luszczek, 2013.
205*> An improved parallel singular value algorithm and its implementation
206*> for multicore hardware, In Proceedings of 2013 International Conference
207*> for High Performance Computing, Networking, Storage and Analysis (SC '13).
208*> Denver, Colorado, USA, 2013.
209*> Article 90, 12 pages.
210*> http://doi.acm.org/10.1145/2503210.2503292
211*>
212*> A. Haidar, R. Solca, S. Tomov, T. Schulthess and J. Dongarra.
213*> A novel hybrid CPU-GPU generalized eigensolver for electronic structure
214*> calculations based on fine-grained memory aware tasks.
215*> International Journal of High Performance Computing Applications.
216*> Volume 28 Issue 2, Pages 196-209, May 2014.
217*> http://hpc.sagepub.com/content/28/2/196
218*>
219*> \endverbatim
220*>
221* =====================================================================
222 SUBROUTINE dsytrd_2stage( VECT, UPLO, N, A, LDA, D, E, TAU,
223 $ HOUS2, LHOUS2, WORK, LWORK, INFO )
224*
225 IMPLICIT NONE
226*
227* -- LAPACK computational routine --
228* -- LAPACK is a software package provided by Univ. of Tennessee, --
229* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
230*
231* .. Scalar Arguments ..
232 CHARACTER VECT, UPLO
233 INTEGER N, LDA, LWORK, LHOUS2, INFO
234* ..
235* .. Array Arguments ..
236 DOUBLE PRECISION D( * ), E( * )
237 DOUBLE PRECISION A( LDA, * ), TAU( * ),
238 $ hous2( * ), work( * )
239* ..
240*
241* =====================================================================
242* ..
243* .. Local Scalars ..
244 LOGICAL LQUERY, UPPER, WANTQ
245 INTEGER KD, IB, LWMIN, LHMIN, LWRK, LDAB, WPOS, ABPOS
246* ..
247* .. External Subroutines ..
249* ..
250* .. External Functions ..
251 LOGICAL LSAME
252 INTEGER ILAENV2STAGE
253 EXTERNAL lsame, ilaenv2stage
254* ..
255* .. Executable Statements ..
256*
257* Test the input parameters
258*
259 info = 0
260 wantq = lsame( vect, 'V' )
261 upper = lsame( uplo, 'U' )
262 lquery = ( lwork.EQ.-1 ) .OR. ( lhous2.EQ.-1 )
263*
264* Determine the block size, the workspace size and the hous size.
265*
266 kd = ilaenv2stage( 1, 'DSYTRD_2STAGE', vect, n, -1, -1, -1 )
267 ib = ilaenv2stage( 2, 'DSYTRD_2STAGE', vect, n, kd, -1, -1 )
268 lhmin = ilaenv2stage( 3, 'DSYTRD_2STAGE', vect, n, kd, ib, -1 )
269 lwmin = ilaenv2stage( 4, 'DSYTRD_2STAGE', vect, n, kd, ib, -1 )
270* WRITE(*,*),'DSYTRD_2STAGE N KD UPLO LHMIN LWMIN ',N, KD, UPLO,
271* $ LHMIN, LWMIN
272*
273 IF( .NOT.lsame( vect, 'N' ) ) THEN
274 info = -1
275 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
276 info = -2
277 ELSE IF( n.LT.0 ) THEN
278 info = -3
279 ELSE IF( lda.LT.max( 1, n ) ) THEN
280 info = -5
281 ELSE IF( lhous2.LT.lhmin .AND. .NOT.lquery ) THEN
282 info = -10
283 ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
284 info = -12
285 END IF
286*
287 IF( info.EQ.0 ) THEN
288 hous2( 1 ) = lhmin
289 work( 1 ) = lwmin
290 END IF
291*
292 IF( info.NE.0 ) THEN
293 CALL xerbla( 'DSYTRD_2STAGE', -info )
294 RETURN
295 ELSE IF( lquery ) THEN
296 RETURN
297 END IF
298*
299* Quick return if possible
300*
301 IF( n.EQ.0 ) THEN
302 work( 1 ) = 1
303 RETURN
304 END IF
305*
306* Determine pointer position
307*
308 ldab = kd+1
309 lwrk = lwork-ldab*n
310 abpos = 1
311 wpos = abpos + ldab*n
312 CALL dsytrd_sy2sb( uplo, n, kd, a, lda, work( abpos ), ldab,
313 $ tau, work( wpos ), lwrk, info )
314 IF( info.NE.0 ) THEN
315 CALL xerbla( 'DSYTRD_SY2SB', -info )
316 RETURN
317 END IF
318 CALL dsytrd_sb2st( 'Y', vect, uplo, n, kd,
319 $ work( abpos ), ldab, d, e,
320 $ hous2, lhous2, work( wpos ), lwrk, info )
321 IF( info.NE.0 ) THEN
322 CALL xerbla( 'DSYTRD_SB2ST', -info )
323 RETURN
324 END IF
325*
326*
327 hous2( 1 ) = lhmin
328 work( 1 ) = lwmin
329 RETURN
330*
331* End of DSYTRD_2STAGE
332*
333 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsytrd_2stage(vect, uplo, n, a, lda, d, e, tau, hous2, lhous2, work, lwork, info)
DSYTRD_2STAGE
subroutine dsytrd_sb2st(stage1, vect, uplo, n, kd, ab, ldab, d, e, hous, lhous, work, lwork, info)
DSYTRD_SB2ST reduces a real symmetric band matrix A to real symmetric tridiagonal form T
subroutine dsytrd_sy2sb(uplo, n, kd, a, lda, ab, ldab, tau, work, lwork, info)
DSYTRD_SY2SB