LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zhetrd_2stage()

subroutine zhetrd_2stage ( character  vect,
character  uplo,
integer  n,
complex*16, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  d,
double precision, dimension( * )  e,
complex*16, dimension( * )  tau,
complex*16, dimension( * )  hous2,
integer  lhous2,
complex*16, dimension( * )  work,
integer  lwork,
integer  info 
)

ZHETRD_2STAGE

Download ZHETRD_2STAGE + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZHETRD_2STAGE reduces a complex Hermitian matrix A to real symmetric
 tridiagonal form T by a unitary similarity transformation:
 Q1**H Q2**H* A * Q2 * Q1 = T.
Parameters
[in]VECT
          VECT is CHARACTER*1
          = 'N':  No need for the Housholder representation,
                  in particular for the second stage (Band to
                  tridiagonal) and thus LHOUS2 is of size max(1, 4*N);
          = 'V':  the Householder representation is needed to
                  either generate Q1 Q2 or to apply Q1 Q2,
                  then LHOUS2 is to be queried and computed.
                  (NOT AVAILABLE IN THIS RELEASE).
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]A
          A is COMPLEX*16 array, dimension (LDA,N)
          On entry, the Hermitian matrix A.  If UPLO = 'U', the leading
          N-by-N upper triangular part of A contains the upper
          triangular part of the matrix A, and the strictly lower
          triangular part of A is not referenced.  If UPLO = 'L', the
          leading N-by-N lower triangular part of A contains the lower
          triangular part of the matrix A, and the strictly upper
          triangular part of A is not referenced.
          On exit, if UPLO = 'U', the band superdiagonal
          of A are overwritten by the corresponding elements of the
          internal band-diagonal matrix AB, and the elements above
          the KD superdiagonal, with the array TAU, represent the unitary
          matrix Q1 as a product of elementary reflectors; if UPLO
          = 'L', the diagonal and band subdiagonal of A are over-
          written by the corresponding elements of the internal band-diagonal
          matrix AB, and the elements below the KD subdiagonal, with
          the array TAU, represent the unitary matrix Q1 as a product
          of elementary reflectors. See Further Details.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[out]D
          D is DOUBLE PRECISION array, dimension (N)
          The diagonal elements of the tridiagonal matrix T.
[out]E
          E is DOUBLE PRECISION array, dimension (N-1)
          The off-diagonal elements of the tridiagonal matrix T.
[out]TAU
          TAU is COMPLEX*16 array, dimension (N-KD)
          The scalar factors of the elementary reflectors of
          the first stage (see Further Details).
[out]HOUS2
          HOUS2 is COMPLEX*16 array, dimension (LHOUS2)
          Stores the Householder representation of the stage2
          band to tridiagonal.
[in]LHOUS2
          LHOUS2 is INTEGER
          The dimension of the array HOUS2.
          If LWORK = -1, or LHOUS2 = -1,
          then a query is assumed; the routine
          only calculates the optimal size of the HOUS2 array, returns
          this value as the first entry of the HOUS2 array, and no error
          message related to LHOUS2 is issued by XERBLA.
          If VECT='N', LHOUS2 = max(1, 4*n);
          if VECT='V', option not yet available.
[out]WORK
          WORK is COMPLEX*16 array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK. LWORK = MAX(1, dimension)
          If LWORK = -1, or LHOUS2=-1,
          then a workspace query is assumed; the routine
          only calculates the optimal size of the WORK array, returns
          this value as the first entry of the WORK array, and no error
          message related to LWORK is issued by XERBLA.
          LWORK = MAX(1, dimension) where
          dimension   = max(stage1,stage2) + (KD+1)*N
                      = N*KD + N*max(KD+1,FACTOPTNB)
                        + max(2*KD*KD, KD*NTHREADS)
                        + (KD+1)*N
          where KD is the blocking size of the reduction,
          FACTOPTNB is the blocking used by the QR or LQ
          algorithm, usually FACTOPTNB=128 is a good choice
          NTHREADS is the number of threads used when
          openMP compilation is enabled, otherwise =1.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Implemented by Azzam Haidar.

  All details are available on technical report, SC11, SC13 papers.

  Azzam Haidar, Hatem Ltaief, and Jack Dongarra.
  Parallel reduction to condensed forms for symmetric eigenvalue problems
  using aggregated fine-grained and memory-aware kernels. In Proceedings
  of 2011 International Conference for High Performance Computing,
  Networking, Storage and Analysis (SC '11), New York, NY, USA,
  Article 8 , 11 pages.
  http://doi.acm.org/10.1145/2063384.2063394

  A. Haidar, J. Kurzak, P. Luszczek, 2013.
  An improved parallel singular value algorithm and its implementation
  for multicore hardware, In Proceedings of 2013 International Conference
  for High Performance Computing, Networking, Storage and Analysis (SC '13).
  Denver, Colorado, USA, 2013.
  Article 90, 12 pages.
  http://doi.acm.org/10.1145/2503210.2503292

  A. Haidar, R. Solca, S. Tomov, T. Schulthess and J. Dongarra.
  A novel hybrid CPU-GPU generalized eigensolver for electronic structure
  calculations based on fine-grained memory aware tasks.
  International Journal of High Performance Computing Applications.
  Volume 28 Issue 2, Pages 196-209, May 2014.
  http://hpc.sagepub.com/content/28/2/196

Definition at line 222 of file zhetrd_2stage.f.

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 COMPLEX*16 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, 'ZHETRD_2STAGE', vect, n, -1, -1, -1 )
267 ib = ilaenv2stage( 2, 'ZHETRD_2STAGE', vect, n, kd, -1, -1 )
268 lhmin = ilaenv2stage( 3, 'ZHETRD_2STAGE', vect, n, kd, ib, -1 )
269 lwmin = ilaenv2stage( 4, 'ZHETRD_2STAGE', vect, n, kd, ib, -1 )
270* WRITE(*,*),'ZHETRD_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( 'ZHETRD_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 zhetrd_he2hb( uplo, n, kd, a, lda, work( abpos ), ldab,
313 $ tau, work( wpos ), lwrk, info )
314 IF( info.NE.0 ) THEN
315 CALL xerbla( 'ZHETRD_HE2HB', -info )
316 RETURN
317 END IF
318 CALL zhetrd_hb2st( '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( 'ZHETRD_HB2ST', -info )
323 RETURN
324 END IF
325*
326*
327 hous2( 1 ) = lhmin
328 work( 1 ) = lwmin
329 RETURN
330*
331* End of ZHETRD_2STAGE
332*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zhetrd_hb2st(stage1, vect, uplo, n, kd, ab, ldab, d, e, hous, lhous, work, lwork, info)
ZHETRD_HB2ST reduces a complex Hermitian band matrix A to real symmetric tridiagonal form T
subroutine zhetrd_he2hb(uplo, n, kd, a, lda, ab, ldab, tau, work, lwork, info)
ZHETRD_HE2HB
integer function ilaenv2stage(ispec, name, opts, n1, n2, n3, n4)
ILAENV2STAGE
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: