Program f08wpfe

!     F08WPF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: f06bnf, nag_wp, x02ajf, x02amf, zggevx
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nb = 64, nin = 5, nout = 6
!     .. Local Scalars ..
      Complex (Kind=nag_wp)            :: eig
      Real (Kind=nag_wp)               :: abnorm, abnrm, bbnrm, eps, small, tol
      Integer                          :: i, ihi, ilo, info, j, lda, ldb,      &
                                          ldvr, lwork, n
!     .. Local Arrays ..
      Complex (Kind=nag_wp), Allocatable :: a(:,:), alpha(:), b(:,:), beta(:), &
                                            vr(:,:), work(:)
      Complex (Kind=nag_wp)            :: dummy(1,1)
      Real (Kind=nag_wp), Allocatable  :: lscale(:), rconde(:), rcondv(:),     &
                                          rscale(:), rwork(:)
      Integer, Allocatable             :: iwork(:)
      Logical, Allocatable             :: bwork(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs, max, nint, real
!     .. Executable Statements ..
      Write (nout,*) 'F08WPF Example Program Results'
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n
      lda = n
      ldb = n
      ldvr = n
      Allocate (a(lda,n),alpha(n),b(ldb,n),beta(n),vr(ldvr,n),lscale(n), &
        rconde(n),rcondv(n),rscale(n),rwork(6*n),iwork(n+2),bwork(n))

!     Use routine workspace query to get optimal workspace.
      lwork = -1
!     The NAG name equivalent of zggevx is f08wpf
      Call zggevx('Balance','No vectors (left)','Vectors (right)', &
        'Both reciprocal condition numbers',n,a,lda,b,ldb,alpha,beta,dummy,1, &
        vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,dummy,lwork, &
        rwork,iwork,bwork,info)

!     Make sure that there is enough workspace for blocksize nb.
      lwork = max((nb+2*n)*n,nint(real(dummy(1,1))))
      Allocate (work(lwork))

!     Read in the matrices A and B

      Read (nin,*)(a(i,1:n),i=1,n)
      Read (nin,*)(b(i,1:n),i=1,n)

!     Solve the generalized eigenvalue problem

!     The NAG name equivalent of zggevx is f08wpf
      Call zggevx('Balance','No vectors (left)','Vectors (right)', &
        'Both reciprocal condition numbers',n,a,lda,b,ldb,alpha,beta,dummy,1, &
        vr,ldvr,ilo,ihi,lscale,rscale,abnrm,bbnrm,rconde,rcondv,work,lwork, &
        rwork,iwork,bwork,info)

      If (info>0) Then
        Write (nout,*)
        Write (nout,99999) 'Failure in ZGGEVX. INFO =', info
      Else

!       Compute the machine precision, the safe range parameter
!       SMALL and sqrt(ABNRM**2+BBNRM**2)

        eps = x02ajf()
        small = x02amf()
        abnorm = f06bnf(abnrm,bbnrm)
        tol = eps*abnorm

!       Print out eigenvalues and vectors and associated condition
!       number and bounds

        Write (nout,*)
        Write (nout,*) 'Eigenvalues'
        Write (nout,*)
        Write (nout,*) '         Eigenvalue           rcond    error'

        Do j = 1, n

!         Print out information on the jth eigenvalue

          If ((abs(alpha(j)))*small>=abs(beta(j))) Then
            If (rconde(j)>0.0_nag_wp) Then
              If (tol/rconde(j)<100.0_nag_wp*eps) Then
                Write (nout,99995) j, rconde(j), '-'
              Else
                Write (nout,99994) j, rconde(j), tol/rconde(j)
              End If
            Else
              Write (nout,99995) j, rconde(j), 'Inf'
            End If
          Else
            eig = alpha(j)/beta(j)
            If (rconde(j)>0.0_nag_wp) Then
              If (tol/rconde(j)<100.0_nag_wp*eps) Then
                Write (nout,99998) j, eig, rconde(j), '-'
              Else
                Write (nout,99997) j, eig, rconde(j), tol/rconde(j)
              End If
            Else
              Write (nout,99998) j, eig, rconde(j), 'Inf'
            End If
          End If

        End Do


        Write (nout,*)
        Write (nout,*) 'Eigenvectors'
        Write (nout,*)
        Write (nout,*) '         Eigenvector          rcond    error'

        Do j = 1, n

!         Print information on jth eigenvector
          Write (nout,*)

!         Make first real part component be positive
          If (real(vr(1,j))<0.0_nag_wp) Then
            vr(1:n,j) = -vr(1:n,j)
          End If

          If (rcondv(j)>0.0_nag_wp) Then
            If (tol/rcondv(j)<100.0_nag_wp*eps) Then
              Write (nout,99998) j, vr(1,j), rcondv(j), '-'
            Else
              Write (nout,99997) j, vr(1,j), rcondv(j), tol/rcondv(j)
            End If
          Else
            Write (nout,99998) j, vr(1,j), rcondv(j), 'Inf'
          End If

          Write (nout,99996) vr(2:n,j)

        End Do

        Write (nout,*)
        Write (nout,*) 'Errors below 100*machine precision are not displayed'
      End If

99999 Format (1X,A,I4)
99998 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,4X,A)
99997 Format (1X,I2,1X,'(',1P,E11.4,',',E11.4,')',1X,0P,F7.4,1X,1P,E8.1)
99996 Format (1X,3X,'(',1P,E11.4,',',E11.4,')')
99995 Format (1X,I2,1X,'  Infinite or undetermined',1X,0P,F7.4,4X,A)
99994 Format (1X,I2,1X,'  Infinite or undetermined',1X,0P,F7.4,1X,1P,E8.1)

    End Program f08wpfe