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

NAG FL Interface Introduction
Example description
    Program g07dbfe

!     G07DBF Example Program Text

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: g07dbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: c, dchi, h1, h2, h3, sigma, sigsav,  &
                                          thesav, theta, tol
      Integer                          :: ifail, ipsi, isigma, maxit, n, nit
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: rs(:), wrk(:), x(:)
!     .. Executable Statements ..
      Write (nout,*) 'G07DBF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) n

      Allocate (x(n),rs(n),wrk(n))

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

!     Read in details of algorithm to use
      Read (nin,*) ipsi, dchi, maxit
      If (ipsi==2) Then
        Read (nin,*) h1, h2, h3
      End If

!     Display titles
      Write (nout,*) '          Input parameters     Output parameters'
      Write (nout,*) 'ISIGMA   SIGMA   THETA   TOL    SIGMA  THETA'

d_lp: Do
        Read (nin,*,Iostat=ifail) isigma, sigma, theta, tol
        If (ifail/=0) Then
          Exit d_lp
        End If

!       Save the input parameters for later display
        sigsav = sigma
        thesav = theta

!       Compute M-estimates
        ifail = 0
        Call g07dbf(isigma,n,x,ipsi,c,h1,h2,h3,dchi,theta,sigma,maxit,tol,rs,  &
          nit,wrk,ifail)

!       Display results
        Write (nout,99999) isigma, sigsav, thesav, tol, sigma, theta
      End Do d_lp

99999 Format (1X,I3,3X,2F8.4,F7.4,F9.4,F8.4,I4)
    End Program g07dbfe