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

NAG FL Interface Introduction
Example description
    Program g07bffe

!     G07BFF Example Program Text

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use nag_library, Only: g07bff, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: beta, ll, xi
      Integer                          :: ifail, n, optopt
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: asvc(4), obsvc(4)
      Real (Kind=nag_wp), Allocatable  :: y(:)
!     .. Executable Statements ..
      Write (nout,*) 'G07BFF Example Program Results'
      Write (nout,*)

!     Skip header
      Read (nin,*)

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

      Allocate (y(n))

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

!     Calculate the GPD parameter estimates
      ifail = 1
      Call g07bff(n,y,optopt,xi,beta,asvc,obsvc,ll,ifail)
      If (ifail/=0) Then
        If (ifail/=6 .And. ifail/=7 .And. ifail/=8) Then
          Write (*,99997) '** G07BFF returned with IFAIL = ', ifail
          Go To 100
        End If
      End If

!     Display parameter estimates
      Write (nout,*) 'Parameter estimates'
      Write (nout,Fmt=99998) 'xi            ', xi
      Write (nout,Fmt=99998) 'beta          ', beta
      Write (nout,*)

!     Display parameter distribution
      If (optopt>0) Then
        If (ifail==7 .Or. ifail==8) Then
          Write (nout,Fmt=99999) 'Invalid observed distribution'
        Else
          Write (nout,*) 'Observed distribution'
          Write (nout,Fmt=99998) 'Var(xi)         ', obsvc(1)
          Write (nout,Fmt=99998) 'Var(beta)       ', obsvc(4)
          Write (nout,Fmt=99998) 'Covar(xi,beta)  ', obsvc(2)
          Write (nout,Fmt=99998) 'Final log-likelihood:', ll
        End If
        Write (nout,*)

      Else
        If (ifail==6 .Or. ifail==7) Then
          Write (nout,Fmt=99999) 'Invalid asymptotic distribution'
        Else
          Write (nout,*) 'Asymptotic distribution'
          Write (nout,Fmt=99998) 'Var(xi)         ', asvc(1)
          Write (nout,Fmt=99998) 'Var(beta)       ', asvc(4)
          Write (nout,Fmt=99998) 'Covar(xi,beta)  ', asvc(2)
        End If
      End If

100   Continue

99999 Format (1X,A)
99998 Format (1X,A,1X,E14.6)
99997 Format (1X,A,I0)
    End Program g07bffe