NAG Library Manual, Mark 27.2
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program f08ntfe

!     F08NTF Example Program Text

!     Mark 27.2 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use nag_library, Only: nag_wp, x02ajf, x04dbf, zgehrd, zgemm, zhseqr,    &
                             zlange => f06uaf, zunghr
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Complex (Kind=nag_wp)            :: alpha, beta
      Real (Kind=nag_wp)               :: norm
      Integer                          :: i, ifail, info, lda, ldc, ldd, ldz,  &
                                          lwork, n
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: a(:,:), c(:,:), d(:,:), tau(:),    &
                                          w(:), work(:), z(:,:)
      Real (Kind=nag_wp), Allocatable  :: rwork(:)
      Character (1)                    :: clabs(1), rlabs(1)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: cmplx
!     .. Executable Statements ..
      Write (nout,*) 'F08NTF Example Program Results'
      Write (nout,*)
      Flush (nout)
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n
      lda = n
      ldc = n
      ldd = n
      ldz = n
      lwork = 64*(n-1)
      Allocate (a(lda,n),c(ldc,n),d(ldd,n),rwork(lda),tau(n),w(n),work(lwork), &
        z(ldz,n))

!     Read A from data file
      Read (nin,*)(a(i,1:n),i=1,n)

!     Store A in D
      d(1:ldd,1:n) = a(1:lda,1:n)

!     Print matrix A
!     ifail: behaviour on error exit
!            =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
      ifail = 0
      Call x04dbf('General',' ',n,n,a,lda,'Bracketed','F7.4','Matrix A',       &
        'Integer',rlabs,'Integer',clabs,80,0,ifail)
      Write (nout,*)
      Flush (nout)

!     Reduce A to upper Hessenberg form H = (Q**H)*A*Q

!     The NAG name equivalent of zgehrd is f08nsf
      Call zgehrd(n,1,n,a,lda,tau,work,lwork,info)

!     Copy A into Z
      z(1:n,1:n) = a(1:n,1:n)

!     Form Q explicitly, storing the result in Z
!     The NAG name equivalent of zunghr is f08ntf
      Call zunghr(n,1,n,z,ldz,tau,work,lwork,info)

!     Calculate the Schur factorization of H = Y*T*(Y**H) and form
!     Q*Y explicitly, storing the result in Z

!     Note that A = Z*T*(Z**H), where Z = Q*Y

!     The NAG name equivalent of zhseqr is f08psf
      Call zhseqr('Schur form','Vectors',n,1,n,a,lda,w,z,ldz,work,lwork,info)

!     Compute A - Z*T*Z^H from Schur factorization of A, and store in matrix D
!     The NAG name equivalent of zgemm is f06zaf
      alpha = cmplx(1,kind=nag_wp)
      beta = cmplx(0,kind=nag_wp)
      Call zgemm('N','N',n,n,n,alpha,z,ldz,a,lda,beta,c,ldc)
      alpha = cmplx(-1,kind=nag_wp)
      beta = cmplx(1,kind=nag_wp)
      Call zgemm('N','C',n,n,n,alpha,c,ldc,z,ldz,beta,d,ldd)

!     Find norm of matrix D and print warning if it is too large
!     f06uaf is the NAG name equivalent of the LAPACK auxiliary zlange
      norm = zlange('O',ldd,n,d,ldd,rwork)
      If (norm>x02ajf()**0.5_nag_wp) Then
        Write (nout,*) 'Norm of A-(Z*T*Z^H) is much greater than 0.'
        Write (nout,*) 'Schur factorization has failed.'
      Else
!       Print eigenvalues.
        Write (nout,*) 'Eigenvalues'
        Write (nout,99999)(w(i),i=1,n)
      End If

99999 Format ((3X,4(' (',F7.4,',',F7.4,')',:)))

    End Program f08ntfe