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

NAG AD Library Introduction
Example description
    Program f08ga_p0w_fe

!     F08GA_P0W_F Example Program Text
!     Mark 28.6 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: f08ga_p0w_f
      Use nag_library, Only: nag_wp, x02ajf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
      Character (1), Parameter         :: uplo = 'U'
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Real (Kind=nag_wp)               :: eerrbd, eps
      Integer                          :: i, ifail, j, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: ap(:), w(:), work(:)
      Real (Kind=nag_wp)               :: dummy(1,1)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: abs, max
!     .. Executable Statements ..
      Write (nout,*) 'F08GA_P0W_F Example Program Results'
      Write (nout,*)
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n

      Allocate (ap((n*(n+1))/2),w(n),work(3*n))

      ifail = 0
!     Read the upper triangular part of the matrix A from data file
      Read (nin,*)((ap(i+(j*(j-1))/2),j=i,n),i=1,n)

!     Solve the symmetric eigenvalue problem
!     The NAG name equivalent of dspev is f08ga_p0w_f
      ifail = 0
      Call f08ga_p0w_f(ad_handle,'No vectors',uplo,n,ap,w,dummy,1,work,ifail)

!     Print solution

      Write (nout,*) 'Eigenvalues'
      Write (nout,99999) w(1:n)

!     Get the machine precision, EPS and compute the approximate
!     error bound for the computed eigenvalues.  Note that for
!     the 2-norm, max( abs(W(i)) ) = norm(A), and since the
!     eigenvalues are returned in ascending order
!     max( abs(W(i)) ) = max( abs(W(1)), abs(W(n)))

      eps = x02ajf()
      eerrbd = eps*max(abs(w(1)),abs(w(n)))

!     Print the approximate error bound for the eigenvalues

      Write (nout,*)
      Write (nout,*) 'Error estimate for the eigenvalues'
      Write (nout,99998) eerrbd

99999 Format (3X,(8F8.4))
99998 Format (4X,1P,6E11.1)
    End Program f08ga_p0w_fe