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

NAG FL Interface Introduction
Example description
    Program g02hkfe

!     G02HKF Example Program Text

!     Mark 27.3 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use nag_library, Only: g02hkf, nag_wp, x04abf, x04ccf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: iset = 1, nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: eps, tol
      Integer                          :: i, ifail, j, ldx, m, maxit, n, nadv, &
                                          nit, nitmon
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: cov(:), theta(:), wk(:), x(:,:)
!     .. Executable Statements ..
      Write (nout,*) 'G02HKF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Read in the problem size and control parameters
      Read (nin,*) n, m

      ldx = n
      Allocate (x(ldx,m),cov(m*(m+1)/2),theta(m),wk(n+m*(m+5)/2))

!     Read in data
      Read (nin,*)(x(i,1:m),i=1,n)

!     Read in the control parameters
      Read (nin,*) nitmon, maxit, tol, eps

!     Set the advisory channel to NOUT for monitoring information
      If (nitmon/=0) Then
        nadv = nout
        Call x04abf(iset,nadv)
      End If

!     Compute robust estimate of variance / covariance matrix
      ifail = 0
      Call g02hkf(n,m,x,ldx,eps,cov,theta,maxit,nitmon,tol,nit,wk,ifail)

!     Display results
      Write (nout,99999) 'G02HKF required ', nit, ' iterations to converge'
      Write (nout,*)
      Flush (nout)
      ifail = 0
      Call x04ccf('Upper','Non-Unit',m,cov,'Covariance matrix',ifail)
      Write (nout,*)
      Write (nout,*) 'THETA'
      Write (nout,99998)(theta(j),j=1,m)

99999 Format (1X,A,I0,A)
99998 Format (1X,F10.3)
    End Program g02hkfe