Example description
    Program g02gnfe

!     G02GNF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g02gcf, g02gnf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: a, dev, eps, sestat, stat, tol, z
      Integer                          :: i, idf, ifail, ip, iprint, irank,    &
                                          ldv, ldx, lwk, lwt, m, maxit, n
      Logical                          :: est
      Character (1)                    :: link, mean, offset, weight
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: b(:), cov(:), f(:), se(:), v(:,:),   &
                                          wk(:), wt(:), x(:,:), y(:)
      Integer, Allocatable             :: isx(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: count, max
!     .. Executable Statements ..
      Write (nout,*) 'G02GNF Example Program Results'
      Write (nout,*)

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

!     Read in the problem size
      Read (nin,*) link, mean, offset, weight, n, m

      If (weight=='W' .Or. weight=='w') Then
        lwt = n
      Else
        lwt = 0
      End If
      ldx = n
      Allocate (x(ldx,m),y(n),wt(lwt),isx(m))

!     Read in data
      If (lwt>0) Then
        Read (nin,*)(x(i,1:m),y(i),wt(i),i=1,n)
      Else
        Read (nin,*)(x(i,1:m),y(i),i=1,n)
      End If

!     Read in variable inclusion flags
      Read (nin,*) isx(1:m)

!     Calculate IP
      ip = count(isx(1:m)>0)
      If (mean=='M' .Or. mean=='m') Then
        ip = ip + 1
      End If

!     Read in power for exponential link
      If (link=='E' .Or. link=='e') Then
        Read (nin,*) a
      End If

      ldv = n
      lwk = max((ip*ip+3*ip+22)/2,ip)
      Allocate (b(ip),se(ip),cov(ip*(ip+1)/2),v(ldv,ip+7),wk(lwk),f(ip))

!     Read in the offset
      If (offset=='Y' .Or. offset=='y') Then
        Read (nin,*) v(1:n,7)
      End If

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

!     Fit generalized linear model with Poisson errors
      ifail = -1
      Call g02gcf('L','M','N','U',n,x,ldx,m,isx,ip,y,wt,a,dev,idf,b,irank,se,  &
        cov,v,ldv,tol,maxit,iprint,eps,wk,ifail)
      If (ifail/=0) Then
        If (ifail<7) Then
          Go To 100
        End If
      End If

!     Display initial results
      Write (nout,99999) 'Deviance = ', dev
      Write (nout,99998) 'Degrees of freedom = ', idf
      Write (nout,*)
      Write (nout,*) '      Estimate     Standard error'
      Write (nout,*)
      Write (nout,99997)(b(i),se(i),i=1,ip)

!     Estimate the estimable functions
      i = 0
fun_lp: Do
!       Read in the function
        Read (nin,*,Iostat=ifail) f(1:ip)
        If (ifail/=0) Then
          Exit fun_lp
        End If

        i = i + 1

!       Estimate it
        ifail = -1
        Call g02gnf(ip,irank,b,cov,v,ldv,f,est,stat,sestat,z,tol,wk,ifail)
        If (ifail/=0) Then
          If (ifail/=2) Then
            Go To 100
          End If
        End If

!       Display results
        Write (nout,*)
        Write (nout,99996) 'Function ', i
        Write (nout,99995) f(1:ip)
        Write (nout,*)
        If (est) Then
          Write (nout,99994) 'STAT = ', stat, ' SE = ', sestat, ' Z = ', z
        Else
          Write (nout,*) 'Function not estimable'
        End If
      End Do fun_lp

100   Continue

99999 Format (1X,A,E12.4)
99998 Format (1X,A,I2)
99997 Format (1X,2F14.4)
99996 Format (1X,A,I4)
99995 Format (1X,5F8.2)
99994 Format (1X,A,F10.4,A,F10.4,A,F10.4)
    End Program g02gnfe