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

◆ chetrd_2stage()

subroutine chetrd_2stage ( character vect,
character uplo,
integer n,
complex, dimension( lda, * ) a,
integer lda,
real, dimension( * ) d,
real, dimension( * ) e,
complex, dimension( * ) tau,
complex, dimension( * ) hous2,
integer lhous2,
complex, dimension( * ) work,
integer lwork,
integer info )

CHETRD_2STAGE

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

Purpose:
!>
!> CHETRD_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 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 REAL array, dimension (N)
!>          The diagonal elements of the tridiagonal matrix T.
!> 
[out]E
!>          E is REAL array, dimension (N-1)
!>          The off-diagonal elements of the tridiagonal matrix T.
!> 
[out]TAU
!>          TAU is COMPLEX array, dimension (N-KD)
!>          The scalar factors of the elementary reflectors of
!>          the first stage (see Further Details).
!> 
[out]HOUS2
!>          HOUS2 is COMPLEX array, dimension (MAX(1,LHOUS2))
!>          Stores the Householder representation of the stage2
!>          band to tridiagonal.
!> 
[in]LHOUS2
!>          LHOUS2 is INTEGER
!>          The dimension of the array HOUS2.
!>          LHOUS2 >= 1.
!>
!>          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 array, dimension (MAX(1,LWORK))
!>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The dimension of the array WORK.
!>          If N = 0, LWORK >= 1, else 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 225 of file chetrd_2stage.f.

227*
228 IMPLICIT NONE
229*
230* -- LAPACK computational routine --
231* -- LAPACK is a software package provided by Univ. of Tennessee, --
232* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
233*
234* .. Scalar Arguments ..
235 CHARACTER VECT, UPLO
236 INTEGER N, LDA, LWORK, LHOUS2, INFO
237* ..
238* .. Array Arguments ..
239 REAL D( * ), E( * )
240 COMPLEX A( LDA, * ), TAU( * ),
241 $ HOUS2( * ), WORK( * )
242* ..
243*
244* =====================================================================
245* ..
246* .. Local Scalars ..
247 LOGICAL LQUERY, UPPER, WANTQ
248 INTEGER KD, IB, LWMIN, LHMIN, LWRK, LDAB, WPOS, ABPOS
249* ..
250* .. External Subroutines ..
252* ..
253* .. External Functions ..
254 LOGICAL LSAME
255 INTEGER ILAENV2STAGE
256 REAL SROUNDUP_LWORK
258* ..
259* .. Executable Statements ..
260*
261* Test the input parameters
262*
263 info = 0
264 wantq = lsame( vect, 'V' )
265 upper = lsame( uplo, 'U' )
266 lquery = ( lwork.EQ.-1 ) .OR. ( lhous2.EQ.-1 )
267*
268* Determine the block size, the workspace size and the hous size.
269*
270 kd = ilaenv2stage( 1, 'CHETRD_2STAGE', vect, n, -1, -1,
271 $ -1 )
272 ib = ilaenv2stage( 2, 'CHETRD_2STAGE', vect, n, kd, -1,
273 $ -1 )
274 IF( n.EQ.0 ) THEN
275 lhmin = 1
276 lwmin = 1
277 ELSE
278 lhmin = ilaenv2stage( 3, 'CHETRD_2STAGE', vect, n, kd,
279 $ ib, -1 )
280 lwmin = ilaenv2stage( 4, 'CHETRD_2STAGE', vect, n, kd,
281 $ ib, -1 )
282 END IF
283*
284 IF( .NOT.lsame( vect, 'N' ) ) THEN
285 info = -1
286 ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
287 info = -2
288 ELSE IF( n.LT.0 ) THEN
289 info = -3
290 ELSE IF( lda.LT.max( 1, n ) ) THEN
291 info = -5
292 ELSE IF( lhous2.LT.lhmin .AND. .NOT.lquery ) THEN
293 info = -10
294 ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
295 info = -12
296 END IF
297*
298 IF( info.EQ.0 ) THEN
299 hous2( 1 ) = sroundup_lwork( lhmin )
300 work( 1 ) = sroundup_lwork( lwmin )
301 END IF
302*
303 IF( info.NE.0 ) THEN
304 CALL xerbla( 'CHETRD_2STAGE', -info )
305 RETURN
306 ELSE IF( lquery ) THEN
307 RETURN
308 END IF
309*
310* Quick return if possible
311*
312 IF( n.EQ.0 ) THEN
313 work( 1 ) = 1
314 RETURN
315 END IF
316*
317* Determine pointer position
318*
319 ldab = kd+1
320 lwrk = lwork-ldab*n
321 abpos = 1
322 wpos = abpos + ldab*n
323 CALL chetrd_he2hb( uplo, n, kd, a, lda, work( abpos ), ldab,
324 $ tau, work( wpos ), lwrk, info )
325 IF( info.NE.0 ) THEN
326 CALL xerbla( 'CHETRD_HE2HB', -info )
327 RETURN
328 END IF
329 CALL chetrd_hb2st( 'Y', vect, uplo, n, kd,
330 $ work( abpos ), ldab, d, e,
331 $ hous2, lhous2, work( wpos ), lwrk, info )
332 IF( info.NE.0 ) THEN
333 CALL xerbla( 'CHETRD_HB2ST', -info )
334 RETURN
335 END IF
336*
337*
338 work( 1 ) = sroundup_lwork( lwmin )
339 RETURN
340*
341* End of CHETRD_2STAGE
342*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine chetrd_hb2st(stage1, vect, uplo, n, kd, ab, ldab, d, e, hous, lhous, work, lwork, info)
CHETRD_HB2ST reduces a complex Hermitian band matrix A to real symmetric tridiagonal form T
subroutine chetrd_he2hb(uplo, n, kd, a, lda, ab, ldab, tau, work, lwork, info)
CHETRD_HE2HB
integer function ilaenv2stage(ispec, name, opts, n1, n2, n3, n4)
ILAENV2STAGE
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
Here is the call graph for this function:
Here is the caller graph for this function: